pgtype timetz support (assume UTC)

This commit is contained in:
qz 2019-01-29 10:58:37 +03:00
parent 5981e2cc43
commit 2c1beb4275
5 changed files with 21 additions and 1 deletions

View File

@ -18,6 +18,7 @@ module Database.PostgreSQL.Protocol.Codecs.Decoders
, numeric , numeric
, bsText , bsText
, time , time
, timetz
, timestamp , timestamp
, timestamptz , timestamptz
, uuid , uuid
@ -169,6 +170,13 @@ bsText = getByteString
time :: FieldDecoder TimeOfDay time :: FieldDecoder TimeOfDay
time _ = mcsToTimeOfDay <$> getInt64BE time _ = mcsToTimeOfDay <$> getInt64BE
{-# INLINE timetz #-}
timetz :: FieldDecoder TimeOfDay
timetz _ = do
t <- getInt64BE
skipBytes 4
return $ mcsToTimeOfDay t
{-# INLINE timestamp #-} {-# INLINE timestamp #-}
timestamp :: FieldDecoder LocalTime timestamp :: FieldDecoder LocalTime
timestamp _ = microsToLocalTime <$> getInt64BE timestamp _ = microsToLocalTime <$> getInt64BE

View File

@ -14,6 +14,7 @@ module Database.PostgreSQL.Protocol.Codecs.Encoders
, numeric , numeric
, bsText , bsText
, time , time
, timetz
, timestamp , timestamp
, timestamptz , timestamptz
, uuid , uuid
@ -48,7 +49,7 @@ bytea = putByteString
{-# INLINE char #-} {-# INLINE char #-}
char :: Char -> Encode char :: Char -> Encode
char c char c
| ord(c) >= 128 = error "Character code must be below 128" | ord c >= 128 = error "Character code must be below 128"
| otherwise = (putWord8 . fromIntegral . ord) c | otherwise = (putWord8 . fromIntegral . ord) c
{-# INLINE date #-} {-# INLINE date #-}
@ -109,6 +110,10 @@ bsText = putByteString
time :: TimeOfDay -> Encode time :: TimeOfDay -> Encode
time = putInt64BE . timeOfDayToMcs time = putInt64BE . timeOfDayToMcs
{-# INLINE timetz #-}
timetz :: TimeOfDay -> Encode
timetz t = putInt64BE (timeOfDayToMcs t) <> putInt32BE 0
{-# INLINE timestamp #-} {-# INLINE timestamp #-}
timestamp :: LocalTime -> Encode timestamp :: LocalTime -> Encode
timestamp = putInt64BE . localTimeToMicros timestamp = putInt64BE . localTimeToMicros

View File

@ -19,6 +19,7 @@ module Database.PostgreSQL.Protocol.Codecs.PgTypes
, numeric , numeric
, text , text
, time , time
, timetz
, timestamp , timestamp
, timestamptz , timestamptz
, uuid , uuid
@ -92,6 +93,9 @@ text = mkOids 25 1009
time :: Oids time :: Oids
time = mkOids 1083 1183 time = mkOids 1083 1183
timetz :: Oids
timetz = mkOids 1266 1270
timestamp :: Oids timestamp :: Oids
timestamp = mkOids 1114 1115 timestamp = mkOids 1114 1115

View File

@ -7,8 +7,10 @@ module Database.PostgreSQL.Protocol.Codecs.Time
, microsToUTC , microsToUTC
, microsToLocalTime , microsToLocalTime
, mcsToTimeOfDay , mcsToTimeOfDay
, mcsToDiffTime
, intervalToDiffTime , intervalToDiffTime
, diffTimeToInterval , diffTimeToInterval
, diffTimeToMcs
) where ) where
import Data.Int (Int64, Int32, Int64) import Data.Int (Int64, Int32, Int64)

View File

@ -111,6 +111,7 @@ testCodecsEncodeDecode = testGroup "Codecs property 'encode . decode = id'"
, mkCodecTest "numeric" PGT.numeric PE.numeric PD.numeric , mkCodecTest "numeric" PGT.numeric PE.numeric PD.numeric
, mkCodecTest "text" PGT.text PE.bsText PD.bsText , mkCodecTest "text" PGT.text PE.bsText PD.bsText
, mkCodecTest "time" PGT.time PE.time PD.time , mkCodecTest "time" PGT.time PE.time PD.time
, mkCodecTest "timetz" PGT.timetz PE.timetz PD.timetz
, mkCodecTest "timestamp" PGT.timestamp PE.timestamp PD.timestamp , mkCodecTest "timestamp" PGT.timestamp PE.timestamp PD.timestamp
, mkCodecTest "timestamptz" PGT.timestamptz PE.timestamptz PD.timestamptz , mkCodecTest "timestamptz" PGT.timestamptz PE.timestamptz PD.timestamptz
, mkCodecTest "uuid" PGT.uuid PE.uuid PD.uuid , mkCodecTest "uuid" PGT.uuid PE.uuid PD.uuid