Skip to content

Commit fda5e3b

Browse files
author
Anton Gushcha
authored
Merge pull request #23 from quetz/time
pgtype time support
2 parents 883b408 + 2c1beb4 commit fda5e3b

File tree

5 files changed

+43
-3
lines changed

5 files changed

+43
-3
lines changed

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

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,8 @@ module Database.PostgreSQL.Protocol.Codecs.Decoders
1717
, bsJsonBytes
1818
, numeric
1919
, bsText
20+
, time
21+
, timetz
2022
, timestamp
2123
, timestamptz
2224
, uuid
@@ -28,7 +30,7 @@ import Data.ByteString (ByteString)
2830
import Data.Char (chr)
2931
import Data.Int (Int16, Int32, Int64)
3032
import Data.Scientific (Scientific)
31-
import Data.Time (Day, UTCTime, LocalTime, DiffTime)
33+
import Data.Time (Day, UTCTime, LocalTime, DiffTime, TimeOfDay)
3234
import Data.UUID (UUID, fromWords)
3335
import qualified Data.Vector as V
3436

@@ -164,6 +166,17 @@ numeric _ = do
164166
bsText :: FieldDecoder ByteString
165167
bsText = getByteString
166168

169+
{-# INLINE time #-}
170+
time :: FieldDecoder TimeOfDay
171+
time _ = mcsToTimeOfDay <$> getInt64BE
172+
173+
{-# INLINE timetz #-}
174+
timetz :: FieldDecoder TimeOfDay
175+
timetz _ = do
176+
t <- getInt64BE
177+
skipBytes 4
178+
return $ mcsToTimeOfDay t
179+
167180
{-# INLINE timestamp #-}
168181
timestamp :: FieldDecoder LocalTime
169182
timestamp _ = microsToLocalTime <$> getInt64BE

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

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,8 @@ module Database.PostgreSQL.Protocol.Codecs.Encoders
1313
, bsJsonBytes
1414
, numeric
1515
, bsText
16+
, time
17+
, timetz
1618
, timestamp
1719
, timestamptz
1820
, uuid
@@ -23,7 +25,7 @@ import Data.Char (ord)
2325
import Data.Int (Int16, Int32, Int64)
2426
import Data.Monoid ((<>))
2527
import Data.Scientific (Scientific)
26-
import Data.Time (Day, UTCTime, LocalTime, DiffTime)
28+
import Data.Time (Day, UTCTime, LocalTime, DiffTime, TimeOfDay)
2729
import Data.UUID (UUID, toWords)
2830

2931
import Database.PostgreSQL.Protocol.Store.Encode
@@ -47,7 +49,7 @@ bytea = putByteString
4749
{-# INLINE char #-}
4850
char :: Char -> Encode
4951
char c
50-
| ord(c) >= 128 = error "Character code must be below 128"
52+
| ord c >= 128 = error "Character code must be below 128"
5153
| otherwise = (putWord8 . fromIntegral . ord) c
5254

5355
{-# INLINE date #-}
@@ -104,6 +106,14 @@ numeric n =
104106
bsText :: ByteString -> Encode
105107
bsText = putByteString
106108

109+
{-# INLINE time #-}
110+
time :: TimeOfDay -> Encode
111+
time = putInt64BE . timeOfDayToMcs
112+
113+
{-# INLINE timetz #-}
114+
timetz :: TimeOfDay -> Encode
115+
timetz t = putInt64BE (timeOfDayToMcs t) <> putInt32BE 0
116+
107117
{-# INLINE timestamp #-}
108118
timestamp :: LocalTime -> Encode
109119
timestamp = putInt64BE . localTimeToMicros

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

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -18,6 +18,8 @@ module Database.PostgreSQL.Protocol.Codecs.PgTypes
1818
, jsonb
1919
, numeric
2020
, text
21+
, time
22+
, timetz
2123
, timestamp
2224
, timestamptz
2325
, uuid
@@ -88,6 +90,12 @@ numeric = mkOids 1700 1231
8890
text :: Oids
8991
text = mkOids 25 1009
9092

93+
time :: Oids
94+
time = mkOids 1083 1183
95+
96+
timetz :: Oids
97+
timetz = mkOids 1266 1270
98+
9199
timestamp :: Oids
92100
timestamp = mkOids 1114 1115
93101

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

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,11 +2,15 @@ module Database.PostgreSQL.Protocol.Codecs.Time
22
( dayToPgj
33
, utcToMicros
44
, localTimeToMicros
5+
, timeOfDayToMcs
56
, pgjToDay
67
, microsToUTC
78
, microsToLocalTime
9+
, mcsToTimeOfDay
10+
, mcsToDiffTime
811
, intervalToDiffTime
912
, diffTimeToInterval
13+
, diffTimeToMcs
1014
) where
1115

1216
import Data.Int (Int64, Int32, Int64)

tests/Codecs/QuickCheck.hs

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -110,6 +110,8 @@ testCodecsEncodeDecode = testGroup "Codecs property 'encode . decode = id'"
110110
(fmap JsonString <$> PD.bsJsonBytes)
111111
, mkCodecTest "numeric" PGT.numeric PE.numeric PD.numeric
112112
, mkCodecTest "text" PGT.text PE.bsText PD.bsText
113+
, mkCodecTest "time" PGT.time PE.time PD.time
114+
, mkCodecTest "timetz" PGT.timetz PE.timetz PD.timetz
113115
, mkCodecTest "timestamp" PGT.timestamp PE.timestamp PD.timestamp
114116
, mkCodecTest "timestamptz" PGT.timestamptz PE.timestamptz PD.timestamptz
115117
, mkCodecTest "uuid" PGT.uuid PE.uuid PD.uuid
@@ -174,6 +176,9 @@ instance Arbitrary Day where
174176
instance Arbitrary DiffTime where
175177
arbitrary = secondsToDiffTime <$> choose (0, 86400 - 1)
176178

179+
instance Arbitrary TimeOfDay where
180+
arbitrary = timeToTimeOfDay <$> arbitrary
181+
177182
instance Arbitrary LocalTime where
178183
arbitrary = LocalTime <$> arbitrary <*> fmap timeToTimeOfDay arbitrary
179184

0 commit comments

Comments
 (0)