mirror of
https://github.com/postgres-haskell/postgres-wire.git
synced 2024-11-22 05:53:12 +03:00
Decoders for interval
This commit is contained in:
parent
9f2ea70bc3
commit
b286f3cfe5
@ -3,7 +3,7 @@ module Database.PostgreSQL.Protocol.Codecs.Decoders where
|
||||
import Data.Word
|
||||
import Data.Int
|
||||
import Data.Char
|
||||
import Data.Time (Day, UTCTime, LocalTime)
|
||||
import Data.Time (Day, UTCTime, LocalTime, DiffTime)
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.Vector as V
|
||||
|
||||
@ -112,8 +112,9 @@ int4 _ = getInt32BE
|
||||
int8 :: FieldDecoder Int64
|
||||
int8 _ = getInt64BE
|
||||
|
||||
-- interval :: FieldDecoder ?
|
||||
-- interval = undefined
|
||||
{-# INLINE interval #-}
|
||||
interval :: FieldDecoder DiffTime
|
||||
interval _ = intervalToDiffTime <$> getInt64BE <*> getInt32BE <*> getInt32BE
|
||||
|
||||
-- | Decodes representation of JSON as @ByteString@.
|
||||
{-# INLINE bsJsonText #-}
|
||||
|
@ -5,9 +5,11 @@ module Database.PostgreSQL.Protocol.Codecs.Time
|
||||
, pgjToDay
|
||||
, microsToUTC
|
||||
, microsToLocalTime
|
||||
, intervalToDiffTime
|
||||
, diffTimeToInterval
|
||||
) where
|
||||
|
||||
import Data.Int (Int64)
|
||||
import Data.Int (Int64, Int32)
|
||||
import Data.Time (Day(..), UTCTime(..), LocalTime(..), DiffTime, TimeOfDay,
|
||||
picosecondsToDiffTime, timeToTimeOfDay,
|
||||
diffTimeToPicoseconds, timeOfDayToTime)
|
||||
@ -43,6 +45,17 @@ microsToLocalTime mcs =
|
||||
let (d, r) = mcs `divMod` microsInDay
|
||||
in LocalTime (pgjToDay d) (mcsToTimeOfDay r)
|
||||
|
||||
{-# INLINE intervalToDiffTime #-}
|
||||
intervalToDiffTime :: Int64 -> Int32 -> Int32 -> DiffTime
|
||||
intervalToDiffTime mcs days months = picosecondsToDiffTime . mcsToPcs $
|
||||
microsInDay * (fromIntegral months * daysInMonth + fromIntegral days)
|
||||
+ fromIntegral mcs
|
||||
|
||||
-- TODO consider adjusted encoding
|
||||
{-# INLINE diffTimeToInterval #-}
|
||||
diffTimeToInterval :: DiffTime -> (Int64, Int32, Int32)
|
||||
diffTimeToInterval dt = (fromIntegral $ diffTimeToMcs dt, 0, 0)
|
||||
|
||||
--
|
||||
-- Utils
|
||||
--
|
||||
@ -82,3 +95,6 @@ postgresEpoch = 2451545
|
||||
|
||||
microsInDay :: Num a => a
|
||||
microsInDay = 24 * 60 * 60 * 10 ^ 6
|
||||
|
||||
daysInMonth :: Num a => a
|
||||
daysInMonth = 30
|
||||
|
Loading…
Reference in New Issue
Block a user