Skip to content

Commit 9b93cc3

Browse files
Base encoders
1 parent a0d1290 commit 9b93cc3

File tree

3 files changed

+111
-11
lines changed

3 files changed

+111
-11
lines changed

postgres-wire.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ library
3333
, Database.PostgreSQL.Protocol.Store.Encode
3434
, Database.PostgreSQL.Protocol.Store.Decode
3535
, Database.PostgreSQL.Protocol.Codecs.Decoders
36+
, Database.PostgreSQL.Protocol.Codecs.Encoders
3637
, Database.PostgreSQL.Protocol.Codecs.PgTypes
3738
, Database.PostgreSQL.Protocol.Codecs.Time
3839
, Database.PostgreSQL.Protocol.Codecs.Numeric
Lines changed: 100 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,100 @@
1+
module Database.PostgreSQL.Protocol.Codecs.Encoders where
2+
3+
import Data.Word
4+
import Data.Monoid ((<>))
5+
import Data.Int
6+
import Data.Char
7+
import Data.Fixed
8+
import Data.UUID (UUID, toByteString)
9+
import Data.Time (Day, UTCTime, LocalTime, DiffTime)
10+
import qualified Data.ByteString as B
11+
import qualified Data.Vector as V
12+
13+
import Control.Monad
14+
15+
import Database.PostgreSQL.Protocol.Store.Encode
16+
import Database.PostgreSQL.Protocol.Types
17+
import Database.PostgreSQL.Protocol.Codecs.Time
18+
import Database.PostgreSQL.Protocol.Codecs.Numeric
19+
--
20+
-- Primitives
21+
--
22+
23+
{-# INLINE bool #-}
24+
bool :: Bool -> Encode
25+
bool False = putWord8 0
26+
bool True = putWord8 1
27+
28+
{-# INLINE bytea #-}
29+
bytea :: B.ByteString -> Encode
30+
bytea = putByteString
31+
32+
{-# INLINE char #-}
33+
char :: Char -> Encode
34+
char = putWord8 . fromIntegral . ord
35+
36+
{-# INLINE date #-}
37+
date :: Day -> Encode
38+
date = putWord32BE . dayToPgj
39+
40+
{-# INLINE float4 #-}
41+
float4 :: Float -> Encode
42+
float4 = putFloat32BE
43+
44+
{-# INLINE float8 #-}
45+
float8 :: Double -> Encode
46+
float8 = putFloat64BE
47+
48+
{-# INLINE int2 #-}
49+
int2 :: Int16 -> Encode
50+
int2 = putInt16BE
51+
52+
{-# INLINE int4 #-}
53+
int4 :: Int32 -> Encode
54+
int4 = putInt32BE
55+
56+
{-# INLINE int8 #-}
57+
int8 :: Int64 -> Encode
58+
int8 = putInt64BE
59+
60+
{-# INLINE interval #-}
61+
interval :: DiffTime -> Encode
62+
interval v = let (mcs, days, months) = diffTimeToInterval v
63+
in putInt64BE mcs <> putInt32BE days <> putInt32BE months
64+
65+
-- | Encodes representation of JSON as @ByteString@.
66+
{-# INLINE bsJsonText #-}
67+
bsJsonText :: B.ByteString -> Encode
68+
bsJsonText = putByteString
69+
70+
-- | Encodes representation of JSONB as @ByteString@.
71+
{-# INLINE bsJsonBytes #-}
72+
bsJsonBytes :: B.ByteString -> Encode
73+
bsJsonBytes bs = putWord8 1 <> putByteString bs
74+
75+
numeric :: HasResolution a => (Fixed a) -> Encode
76+
numeric _ = do undefined
77+
-- ndigits <- putWord16BE
78+
-- weight <- putInt16BE
79+
-- msign <- numericSign <$> putWord16BE
80+
-- sign <- maybe (fail "unknown numeric") pure msign
81+
-- dscale <- putWord16BE
82+
-- digits <- replicateM (fromIntegral ndigits) putWord16BE
83+
-- pure $ undefined
84+
85+
-- | Encodes text.
86+
{-# INLINE bsText #-}
87+
bsText :: B.ByteString -> Encode
88+
bsText = putByteString
89+
90+
{-# INLINE timestamp #-}
91+
timestamp :: LocalTime -> Encode
92+
timestamp = putWord64BE . localTimeToMicros
93+
94+
{-# INLINE timestamptz #-}
95+
timestamptz :: UTCTime -> Encode
96+
timestamptz = putWord64BE . utcToMicros
97+
98+
{-# INLINE uuid #-}
99+
uuid :: UUID -> Encode
100+
uuid = undefined

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

Lines changed: 10 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -16,18 +16,17 @@ import Data.Time (Day(..), UTCTime(..), LocalTime(..), DiffTime, TimeOfDay,
1616
diffTimeToPicoseconds, timeOfDayToTime)
1717

1818
{-# INLINE dayToPgj #-}
19-
dayToPgj :: Day -> Integer
20-
dayToPgj = (+ (modifiedJulianEpoch - postgresEpoch)) . toModifiedJulianDay
19+
dayToPgj :: Integral a => Day -> a
20+
dayToPgj = fromIntegral
21+
.(+ (modifiedJulianEpoch - postgresEpoch)) . toModifiedJulianDay
2122

2223
{-# INLINE utcToMicros #-}
23-
utcToMicros :: UTCTime -> Word32
24-
utcToMicros (UTCTime day diffTime) = fromIntegral $
25-
dayToMcs day + diffTimeToMcs diffTime
24+
utcToMicros :: UTCTime -> Word64
25+
utcToMicros (UTCTime day diffTime) = dayToMcs day + diffTimeToMcs diffTime
2626

2727
{-# INLINE localTimeToMicros #-}
2828
localTimeToMicros :: LocalTime -> Word64
29-
localTimeToMicros (LocalTime day time) = fromIntegral $
30-
dayToMcs day + timeOfDayToMcs time
29+
localTimeToMicros (LocalTime day time) = dayToMcs day + timeOfDayToMcs time
3130

3231
{-# INLINE pgjToDay #-}
3332
pgjToDay :: Integral a => a -> Day
@@ -61,15 +60,15 @@ diffTimeToInterval dt = (fromIntegral $ diffTimeToMcs dt, 0, 0)
6160
-- Utils
6261
--
6362
{-# INLINE dayToMcs #-}
64-
dayToMcs :: Day -> Integer
63+
dayToMcs :: Integral a => Day -> a
6564
dayToMcs = (microsInDay *) . dayToPgj
6665

6766
{-# INLINE diffTimeToMcs #-}
68-
diffTimeToMcs :: DiffTime -> Integer
69-
diffTimeToMcs = pcsToMcs . diffTimeToPicoseconds
67+
diffTimeToMcs :: Integral a => DiffTime -> a
68+
diffTimeToMcs = fromIntegral . pcsToMcs . diffTimeToPicoseconds
7069

7170
{-# INLINE timeOfDayToMcs #-}
72-
timeOfDayToMcs :: TimeOfDay -> Integer
71+
timeOfDayToMcs :: Integral a => TimeOfDay -> a
7372
timeOfDayToMcs = diffTimeToMcs . timeOfDayToTime
7473

7574
{-# INLINE mcsToDiffTime #-}

0 commit comments

Comments
 (0)