Skip to content

Commit 5a5dbbd

Browse files
Changed Int to Word in codecs
1 parent ff56dec commit 5a5dbbd

File tree

2 files changed

+14
-13
lines changed

2 files changed

+14
-13
lines changed

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

Lines changed: 9 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ dataRowHeader = skipBytes 7
2525

2626
{-# INLINE fieldLength #-}
2727
fieldLength :: Decode Int
28-
fieldLength = fromIntegral <$> getInt32BE
28+
fieldLength = fromIntegral <$> getWord32BE
2929

3030
{-# INLINE getNonNullable #-}
3131
getNonNullable :: FieldDecoder a -> Decode a
@@ -64,7 +64,7 @@ arrayDimensions dims = V.reverse <$> V.replicateM dims arrayDimSize
6464
where
6565
-- 4 bytes - count of elements in dimension
6666
-- 4 bytes - lower bound
67-
arrayDimSize = (fromIntegral <$> getInt32BE) <* getInt32BE
67+
arrayDimSize = (fromIntegral <$> getWord32BE) <* getWord32BE
6868

6969
{-# INLINE arrayFieldDecoder #-}
7070
arrayFieldDecoder :: Int -> (V.Vector Int -> Decode a) -> FieldDecoder a
@@ -91,7 +91,7 @@ char _ = chr . fromIntegral <$> getWord8
9191

9292
{-# INLINE date #-}
9393
date :: FieldDecoder Day
94-
date _ = pgjToDay <$> getInt32BE
94+
date _ = pgjToDay <$> getWord32BE
9595

9696
{-# INLINE float4 #-}
9797
float4 :: FieldDecoder Float
@@ -137,16 +137,16 @@ bsText = getByteString
137137

138138
{-# INLINE timestamp #-}
139139
timestamp :: FieldDecoder LocalTime
140-
timestamp _ = microsToLocalTime <$> getInt64BE
140+
timestamp _ = microsToLocalTime <$> getWord64BE
141141

142142
{-# INLINE timestamptz #-}
143143
timestamptz :: FieldDecoder UTCTime
144-
timestamptz _ = microsToUTC <$> getInt64BE
144+
timestamptz _ = microsToUTC <$> getWord64BE
145145

146146
{-# INLINE uuid #-}
147147
uuid :: FieldDecoder UUID
148148
uuid _ = fromWords
149-
<$> (fromIntegral <$> getInt32BE)
150-
<*> (fromIntegral <$> getInt32BE)
151-
<*> (fromIntegral <$> getInt32BE)
152-
<*> (fromIntegral <$> getInt32BE)
149+
<$> getWord32BE
150+
<*> getWord32BE
151+
<*> getWord32BE
152+
<*> getWord32BE

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

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Database.PostgreSQL.Protocol.Codecs.Time
1010
) where
1111

1212
import Data.Int (Int64, Int32)
13+
import Data.Word (Word32, Word64)
1314
import Data.Time (Day(..), UTCTime(..), LocalTime(..), DiffTime, TimeOfDay,
1415
picosecondsToDiffTime, timeToTimeOfDay,
1516
diffTimeToPicoseconds, timeOfDayToTime)
@@ -19,12 +20,12 @@ dayToPgj :: Day -> Integer
1920
dayToPgj = (+ (modifiedJulianEpoch - postgresEpoch)) . toModifiedJulianDay
2021

2122
{-# INLINE utcToMicros #-}
22-
utcToMicros :: UTCTime -> Int64
23+
utcToMicros :: UTCTime -> Word32
2324
utcToMicros (UTCTime day diffTime) = fromIntegral $
2425
dayToMcs day + diffTimeToMcs diffTime
2526

2627
{-# INLINE localTimeToMicros #-}
27-
localTimeToMicros :: LocalTime -> Int64
28+
localTimeToMicros :: LocalTime -> Word64
2829
localTimeToMicros (LocalTime day time) = fromIntegral $
2930
dayToMcs day + timeOfDayToMcs time
3031

@@ -34,13 +35,13 @@ pgjToDay = ModifiedJulianDay . fromIntegral
3435
. subtract (modifiedJulianEpoch - postgresEpoch)
3536

3637
{-# INLINE microsToUTC #-}
37-
microsToUTC :: Int64 -> UTCTime
38+
microsToUTC :: Word64 -> UTCTime
3839
microsToUTC mcs =
3940
let (d, r) = mcs `divMod` microsInDay
4041
in UTCTime (pgjToDay d) (mcsToDiffTime r)
4142

4243
{-# INLINE microsToLocalTime #-}
43-
microsToLocalTime :: Int64 -> LocalTime
44+
microsToLocalTime :: Word64 -> LocalTime
4445
microsToLocalTime mcs =
4546
let (d, r) = mcs `divMod` microsInDay
4647
in LocalTime (pgjToDay d) (mcsToTimeOfDay r)

0 commit comments

Comments
 (0)