10000 Changed Int to Word in protocol types · postgres-haskell/postgres-wire@ff56dec · GitHub
[go: up one dir, main page]

Skip to content

Commit ff56dec

Browse files
Changed Int to Word in protocol types
1 parent 30c0ad8 commit ff56dec

File tree

5 files changed

+52
-39
lines changed

5 files changed

+52
-39
lines changed

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@
33
-}
44
module Database.PostgreSQL.Protocol.Codecs.PgTypes where
55

6-
import Data.Int (Int32)
6+
import Data.Word (Word32)
77

88
import Database.PostgreSQL.Protocol.Types
99

@@ -12,7 +12,7 @@ data Oids = Oids
1212
, oidArrayType :: {-# UNPACK #-} !Oid
1313
} deriving (Show, Eq)
1414

15-
mkOids :: Int32 -> Int32 -> Oids
15+
mkOids :: Word32 -> Word32 -> Oids
1616
mkOids a b = Oids (Oid a) (Oid b)
1717

1818
--

src/Database/PostgreSQL/Protocol/Decoders.hs

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ decodeAuthResponse = do
5050
(getByteString len >>=
5151
eitherToDecode .parseErrorDesc)
5252
'R' -> do
53-
rType <- getInt32BE
53+
rType <- getWord32BE
5454
case rType of
5555
0 -> pure AuthenticationOk
5656
3 -> pure AuthenticationCleartextPassword
@@ -63,12 +63,12 @@ decodeAuthResponse = do
6363

6464
decodeHeader :: Decode Header
6565
decodeHeader = Header <$> getWord8 <*>
66-
(fromIntegral . subtract 4 <$> getInt32BE)
66+
(fromIntegral . subtract 4 <$> getWord32BE)
6767

6868
decodeServerMessage :: Header -> Decode ServerMessage
6969
decodeServerMessage (Header c len) = case chr $ fromIntegral c of
70-
'K' -> BackendKeyData <$> (ServerProcessId <$> getInt32BE)
71-
<*> (ServerSecretKey <$> getInt32BE)
70+
'K' -> BackendKeyData <$> (ServerProcessId <$> getWord32BE)
71+
<*> (ServerSecretKey <$> getWord32BE)
7272
'2' -> pure BindComplete
7373
'3' -> pure CloseComplete
7474
'C' -> CommandComplete <$> (getByteString len
@@ -87,15 +87,15 @@ decodeServerMessage (Header c len) = case chr $ fromIntegral c of
8787
eitherToDecode . parseNoticeDesc)
8888
'A' -> NotificationResponse <$> decodeNotification
8989
't' -> do
90-
paramCount <- fromIntegral <$> getInt16BE
90+
paramCount <- fromIntegral <$> getWord16BE
9191
ParameterDescription <$> V.replicateM paramCount
92-
(Oid <$> getInt32BE)
92+
(Oid <$> getWord32BE)
9393
'S' -> ParameterStatus <$> getByteStringNull <*> getByteStringNull
9494
'1' -> pure ParseComplete
9595
's' -> pure PortalSuspended
9696
'Z' -> ReadyForQuery <$> decodeTransactionStatus
9797
'T' -> do
98-
rowsCount <- fromIntegral <$> getInt16BE
98+
rowsCount <- fromIntegral <$> getWord16BE
9999
RowDescription <$> V.replicateM rowsCount decodeFieldDescription
100100

101101
decodeTransactionStatus :: Decode TransactionStatus
@@ -109,21 +109,21 @@ decodeTransactionStatus = getWord8 >>= \t ->
109109
decodeFieldDescription :: Decode FieldDescription
110110
decodeFieldDescription = FieldDescription
111111
<$> getByteStringNull
112-
<*> (Oid <$> getInt32BE)
113-
<*> getInt16BE
114-
<*> (Oid <$> getInt32BE)
112+
<*> (Oid <$> getWord32BE)
113+
<*> getWord16BE
114+
<*> (Oid <$> getWord32BE)
115115
<*> getInt16BE
116116
<*> getInt32BE
117117
<*> decodeFormat
118118

119119
decodeNotification :: Decode Notification
120120
decodeNotification = Notification
121-
<$> (ServerProcessId <$> getInt32BE)
121+
<$> (ServerProcessId <$> getWord32BE)
122122
<*> (ChannelName <$> getByteStringNull)
123123
<*> getByteStringNull
124124

125125
decodeFormat :: Decode Format
126-
decodeFormat = getInt16BE >>= \f ->
126+
decodeFormat = getWord16BE >>= \f ->
127127
case f of
128128
0 -> pure Text
129129
1 -> pure Binary

src/Database/PostgreSQL/Protocol/Encoders.hs

Lines changed: 17 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -3,7 +3,7 @@ module Database.PostgreSQL.Protocol.Encoders
33
, encodeClientMessage
44
) where
55

6-
import Data.Int (Int32)
6+
import Data.Word (Word32)
77
import Data.Monoid ((<>))
88
import qualified Data.Vector as V
99
import qualified Data.ByteString as B
@@ -12,19 +12,20 @@ import Database.PostgreSQL.Protocol.Types
1212
import Database.PostgreSQL.Protocol.Store.Encode
1313

1414
-- | Protocol Version 3.0, major version in the first word16.
15-
currentVersion :: Int32
15+
currentVersion :: Word32
1616
currentVersion = 3 * 256 * 256
1717

1818
encodeStartMessage :: StartMessage -> Encode
1919
encodeStartMessage (StartupMessage (Username uname) (DatabaseName dbname))
20-
= putInt32BE (len + 4) <> payload
20+
= putWord32BE (len + 4) <> payload
2121
where
2222
len = fromIntegral $ getEncodeLen payload
23-
payload = putInt32BE currentVersion <>
23+
payload = putWord32BE currentVersion <>
2424
putPgString "user" <> putPgString uname <>
2525
putPgString "database" <> putPgString dbname <> putWord8 0
2626
encodeStartMessage SSLRequest
27-
= putInt32BE 8 <> putInt32BE 80877103 -- value hardcoded by PostgreSQL docs.
27+
-- Value hardcoded by PostgreSQL docs.
28+
= putWord32BE 8 <> putWord32BE 80877103
2829

2930
encodeClientMessage :: ClientMessage -> Encode
3031
encodeClientMessage (Bind (PortalName portalName) (StatementName stmtName)
@@ -33,13 +34,13 @@ encodeClientMessage (Bind (PortalName portalName) (StatementName stmtName)
3334
putPgString portalName <>
3435
putPgString stmtName <>
3536
-- `1` means that the specified format code is applied to all parameters
36-
putInt16BE 1 <>
37+
putWord16BE 1 <>
3738
encodeFormat paramFormat <>
38-
putInt16BE (fromIntegral $ V.length values) <>
39+
putWord16BE (fromIntegral $ V.length values) <>
3940
foldMap encodeValue values <>
4041
-- `1` means that the specified format code is applied to all
4142
-- result columns (if any)
42-
putInt16BE 1 <>
43+
putWord16BE 1 <>
4344
encodeFormat resultFormat
4445
encodeClientMessage (CloseStatement (StatementName stmtName))
4546
= prependHeader 'C' $ putChar8 'S' <> putPgString stmtName
@@ -52,15 +53,15 @@ encodeClientMessage (DescribePortal (PortalName portalName))
5253
encodeClientMessage (Execute (PortalName portalName) (RowsToReceive rows))
5354
= prependHeader 'E' $
5455
putPgString portalName <>
55-
putInt32BE rows
56+
putWord32BE rows
5657
encodeClientMessage Flush
5758
= prependHeader 'H' mempty
5859
encodeClientMessage (Parse (StatementName stmtName) (StatementSQL stmt) oids)
5960
= prependHeader 'P' $
6061
putPgString stmtName <>
6162
putPgString stmt <>
62-
putInt16BE (fromIntegral $ V.length oids) <>
63-
foldMap (putInt32BE . unOid) oids
63+
putWord16BE (fromIntegral $ V.length oids) <>
64+
foldMap (putWord32BE . unOid) oids
6465
encodeClientMessage (PasswordMessage passtext)
6566
= prependHeader 'p' $ putPgString $ getPassword passtext
6667
where
@@ -76,17 +77,17 @@ encodeClientMessage Terminate
7677
-- | Encodes single data values. Length `-1` indicates a NULL parameter value.
7778
-- No value bytes follow in the NULL case.
7879
encodeValue :: Maybe B.ByteString -> Encode
79-
encodeValue Nothing = putInt32BE (-1)
80-
encodeValue (Just v) = putInt32BE (fromIntegral $ B.length v)
80+
encodeValue Nothing = putWord32BE (-1)
81+
encodeValue (Just v) = putWord32BE (fromIntegral $ B.length v)
8182
<> putByteString v
8283

8384
encodeFormat :: Format -> Encode
84-
encodeFormat Text = putInt16BE 0
85-
encodeFormat Binary = putInt16BE 1
85+
encodeFormat Text = putWord16BE 0
86+
encodeFormat Binary = putWord16BE 1
8687

8788
prependHeader :: Char -> Encode -> Encode
8889
prependHeader c payload =
8990
-- Length includes itself but not the first message-type byte
9091
let len = 4 + fromIntegral (getEncodeLen payload)
91-
in putChar8 c <> putInt32BE len <> payload
92+
in putChar8 c <> putWord32BE len <> payload
9293

src/Database/PostgreSQL/Protocol/Store/Decode.hs

Lines changed: 15 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -69,17 +69,29 @@ getByteStringNull = Decode $ Peek $ \ps ptr -> do
6969
getWord8 :: Decode Word8
7070
getWord8 = prim 1 peek
7171

72+
{-# INLINE getWord16BE #-}
73+
getWord16BE :: Decode Word16
74+
getWord16BE = prim 2 $ \ptr -> byteSwap16 <$> peek (castPtr ptr)
75+
76+
{-# INLINE getWord32BE #-}
77+
getWord32BE :: Decode Word32
78+
getWord32BE = prim 4 $ \ptr -> byteSwap32 <$> peek (castPtr ptr)
79+
80+
{-# INLINE getWord64BE #-}
81+
getWord64BE :: Decode Word64
82+
getWord64BE = prim 8 $ \ptr -> byteSwap64 <$> peek (castPtr ptr)
83+
7284
{-# INLINE getInt16BE #-}
7385
getInt16BE :: Decode Int16
74-
getInt16BE = prim 2 $ \ptr -> fromIntegral . byteSwap16 <$> peek (castPtr ptr)
86+
getInt16BE = fromIntegral <$> getWord16BE
7587

7688
{-# INLINE getInt32BE #-}
7789
getInt32BE :: Decode Int32
78-
getInt32BE = prim 4 $ \ptr -> fromIntegral . byteSwap32 <$> peek (castPtr ptr)
90+
getInt32BE = fromIntegral <$> getWord32BE
7991

8092
{-# INLINE getInt64BE #-}
8193
getInt64BE :: Decode Int64
82-
getInt64BE = prim 8 $ \ptr -> fromIntegral . byteSwap64 <$> peek (castPtr ptr)
94+
getInt64BE = fromIntegral <$> getWord64BE
8395

8496
{-# INLINE getFloat32BE #-}
8597
getFloat32BE :: Decode Float

src/Database/PostgreSQL/Protocol/Types.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -10,15 +10,15 @@ module Database.PostgreSQL.Protocol.Types where
1010
-- * bind command can have different formats for parameters and results
1111
-- but we assume that there will be one format for all.
1212

13-
import Data.Word (Word32, Word8)
13+
import Data.Word (Word32, Word8, Word16)
1414
import Data.Int (Int32, Int16)
1515
import Data.Hashable (Hashable)
1616
import Data.ByteString as B(ByteString)
1717
import qualified Data.ByteString.Lazy as BL(ByteString)
1818
import Data.Vector (Vector)
1919

2020
-- Common
21-
newtype Oid = Oid { unOid :: Int32 } deriving (Show, Eq)
21+
newtype Oid = Oid { unOid :: Word32 } deriving (Show, Eq)
2222
newtype StatementName = StatementName ByteString deriving (Show)
2323
newtype StatementSQL = StatementSQL ByteString deriving (Show, Eq, Hashable)
2424
newtype PortalName = PortalName ByteString deriving (Show)
@@ -34,8 +34,8 @@ data PasswordText
3434
| PasswordMD5 !ByteString
3535
deriving (Show)
3636

37-
newtype ServerProcessId = ServerProcessId Int32 deriving (Show)
38-
newtype ServerSecretKey = ServerSecretKey Int32 deriving (Show)
37+
newtype ServerProcessId = ServerProcessId Word32 deriving (Show)
38+
newtype ServerSecretKey = ServerSecretKey Word32 deriving (Show)
3939

4040
-- | Server version contains major, minor, revision numbers.
4141
-- Examples:
@@ -65,7 +65,7 @@ data DataMessage
6565

6666
-- | Maximum number of rows to return, if portal contains a query that
6767
-- returns rows (ignored otherwise). Zero denotes "no limit".
68-
newtype RowsToReceive = RowsToReceive Int32 deriving (Show)
68+
newtype RowsToReceive = RowsToReceive Word32 deriving (Show)
6969

7070
-- | Query will returned unlimited rows.
7171
noLimitToReceive :: RowsToReceive
@@ -200,7 +200,7 @@ data FieldDescription = FieldDescription {
200200
, fieldTableOid :: !Oid
201201
-- | If the field can be identified as a column of a specific table,
202202
-- the attribute number of the column; otherwise zero.
203-
, fieldColumnNumber :: !Int16
203+
, fieldColumnNumber :: !Word16
204204
-- | The object ID of the field's data type.
205205
, fieldTypeOid :: !Oid
206206
-- | The data type size (see pg_type.typlen). Note that negative

0 commit comments

Comments
 (0)
0