@@ -2,6 +2,8 @@ module Database.PostgreSQL.Protocol.Codecs.Decoders where
22
33import Data.Word
44import Data.Int
5+ import Data.Maybe
6+ import Data.Fixed
57import Data.Char
68import Data.UUID (UUID , fromWords )
79import Data.Time (Day , UTCTime , LocalTime , DiffTime )
@@ -14,6 +16,7 @@ import Prelude hiding (bool)
1416import Database.PostgreSQL.Protocol.Store.Decode
1517import Database.PostgreSQL.Protocol.Types
1618import Database.PostgreSQL.Protocol.Codecs.Time
19+ import Database.PostgreSQL.Protocol.Codecs.Numeric
1720
1821-- | Decodes DataRow header.
1922-- 1 byte - Message Header
@@ -62,15 +65,15 @@ arrayHeader = skipBytes 12
6265arrayDimensions :: Int -> Decode (V. Vector Int )
6366arrayDimensions dims = V. reverse <$> V. replicateM dims arrayDimSize
6467 where
65- -- 4 bytes - count of elements in dimension
68+ -- 4 bytes - count of elements in the dimension
6669 -- 4 bytes - lower bound
6770 arrayDimSize = (fromIntegral <$> getWord32BE) <* getWord32BE
6871
6972{-# INLINE arrayFieldDecoder #-}
7073arrayFieldDecoder :: Int -> (V. Vector Int -> Decode a ) -> FieldDecoder a
7174arrayFieldDecoder dims f _ = arrayHeader *> arrayDimensions dims >>= f
7275
73- -- | Decodes only content of a field.
76+ -- | Decodes only a content of the field.
7477type FieldDecoder a = Int -> Decode a
7578
7679--
@@ -103,15 +106,15 @@ float8 _ = getFloat64BE
103106
104107{-# INLINE int2 #-}
105108int2 :: FieldDecoder Int16
106- int2 _ = getInt16BE
109+ int2 _ = getInt16BE
107110
108111{-# INLINE int4 #-}
109112int4 :: FieldDecoder Int32
110- int4 _ = getInt32BE
113+ int4 _ = getInt32BE
111114
112115{-# INLINE int8 #-}
113116int8 :: FieldDecoder Int64
114- int8 _ = getInt64BE
117+ int8 _ = getInt64BE
115118
116119{-# INLINE interval #-}
117120interval :: FieldDecoder DiffTime
@@ -127,8 +130,15 @@ bsJsonText = getByteString
127130bsJsonBytes :: FieldDecoder B. ByteString
128131bsJsonBytes len = getWord8 *> getByteString (len - 1 )
129132
130- -- numeric :: FieldDecoder Scientific
131- -- numeric = undefined
133+ numeric :: HasResolution a => FieldDecoder (Fixed a )
134+ numeric _ = do
135+ ndigits <- getWord16BE
136+ weight <- getInt16BE
137+ msign <- numericSign <$> getWord16BE
138+ sign <- maybe (fail " unknown numeric" ) pure msign
139+ dscale <- getWord16BE
140+ digits <- replicateM (fromIntegral ndigits) getWord16BE
141+ pure $ undefined
132142
133143-- | Decodes text without applying encoding.
134144{-# INLINE bsText #-}
0 commit comments