Skip to content

Commit 856d839

Browse files
Unfinished decoder for Numeric
1 parent 5a5dbbd commit 856d839

File tree

3 files changed

+39
-7
lines changed

3 files changed

+39
-7
lines changed

postgres-wire.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,7 @@ library
3535
, Database.PostgreSQL.Protocol.Codecs.Decoders
3636
, Database.PostgreSQL.Protocol.Codecs.PgTypes
3737
, Database.PostgreSQL.Protocol.Codecs.Time
38+
, Database.PostgreSQL.Protocol.Codecs.Numeric
3839
other-modules: Database.PostgreSQL.Protocol.Utils
3940
build-depends: base >= 4.7 && < 5
4041
, bytestring

src/Database/PostgreSQL/Protocol/Codecs/Decoders.hs

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,8 @@ module Database.PostgreSQL.Protocol.Codecs.Decoders where
22

33
import Data.Word
44
import Data.Int
5+
import Data.Maybe
6+
import Data.Fixed
57
import Data.Char
68
import Data.UUID (UUID, fromWords)
79
import Data.Time (Day, UTCTime, LocalTime, DiffTime)
@@ -14,6 +16,7 @@ import Prelude hiding (bool)
1416
import Database.PostgreSQL.Protocol.Store.Decode
1517
import Database.PostgreSQL.Protocol.Types
1618
import 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
6265
arrayDimensions :: Int -> Decode (V.Vector Int)
6366
arrayDimensions 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 #-}
7073
arrayFieldDecoder :: Int -> (V.Vector Int -> Decode a) -> FieldDecoder a
7174
arrayFieldDecoder dims f _ = arrayHeader *> arrayDimensions dims >>= f
7275

73-
-- | Decodes only content of a field.
76+
-- | Decodes only a content of the field.
7477
type FieldDecoder a = Int -> Decode a
7578

7679
--
@@ -103,15 +106,15 @@ float8 _ = getFloat64BE
103106

104107
{-# INLINE int2 #-}
105108
int2 :: FieldDecoder Int16
106-
int2 _ = getInt16BE
109+
int2 _ = getInt16BE
107110

108111
{-# INLINE int4 #-}
109112
int4 :: FieldDecoder Int32
110-
int4 _ = getInt32BE
113+
int4 _ = getInt32BE
111114

112115
{-# INLINE int8 #-}
113116
int8 :: FieldDecoder Int64
114-
int8 _ = getInt64BE
117+
int8 _ = getInt64BE
115118

116119
{-# INLINE interval #-}
117120
interval :: FieldDecoder DiffTime
@@ -127,8 +130,15 @@ bsJsonText = getByteString
127130
bsJsonBytes :: FieldDecoder B.ByteString
128131
bsJsonBytes 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 #-}
Lines changed: 21 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,21 @@
1+
module Database.PostgreSQL.Protocol.Codecs.Numeric where
2+
3+
-- TODO test it
4+
import Data.Word
5+
import Data.Int
6+
import Data.Foldable
7+
import Data.Fixed
8+
9+
numericDigit :: [Word16] -> Integer
10+
numericDigit = foldl' (\acc n -> acc * nBase + fromIntegral n) 0
11+
12+
numericSign :: Num a => Word16 -> Maybe a
13+
numericSign 0x0000 = Just 1
14+
numericSign 0x4000 = Just $ -1
15+
numericSign _ = Nothing -- NaN code is 0xC000, it is not supported.
16+
17+
fixedFromNumeric :: HasResolution a => Int16 -> [Word16] -> Fixed a
18+
fixedFromNumeric weight digits = undefined
19+
20+
nBase :: Num a => a
21+
nBase = 10000

0 commit comments

Comments
 (0)