8000 Changed sending/receiving value to Maybe to indicate NULL · postgres-haskell/postgres-wire@213bb53 · GitHub
[go: up one dir, main page]

Skip to content

Commit 213bb53

Browse files
Changed sending/receiving value to Maybe to indicate NULL
1 parent 598bf0c commit 213bb53

File tree

7 files changed

+24
-28
lines changed

7 files changed

+24
-28
lines changed

src/Database/PostgreSQL/Driver/Connection.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -44,9 +44,10 @@ type NotificationHandler = Notification -> IO ()
4444
type Dispatcher
4545
= InChan (Either Error DataMessage)
4646
-> ServerMessage
47-
-> [V.Vector B.ByteString]
48-
-> IO [V.Vector B.ByteString]
49-
data DataMessage = DataMessage [V.Vector B.ByteString]
47+
-> [V.Vector (Maybe B.ByteString)]
48+
-> IO [V.Vector (Maybe B.ByteString)]
49+
50+
data DataMessage = DataMessage [V.Vector (Maybe B.ByteString)]
5051
deriving (Show, Eq)
5152

5253
-- | Parameters of the current connection.
@@ -215,14 +216,14 @@ receiverThread
215216
-> IO ()
216217
receiverThread msgFilter rawConn dataChan allChan modeRef = receiveLoop []
217218
where
218-
receiveLoop :: [V.Vector B.ByteString] -> IO ()
219+
receiveLoop :: [V.Vector (Maybe B.ByteString)] -> IO ()
219220
receiveLoop acc = do
220221
r <- rReceive rawConn 4096
221222
-- print r
222223
go r acc >>= receiveLoop
223224

224225
decoder = runGetIncremental decodeServerMessage
225-
go :: B.ByteString -> [V.Vector B.ByteString] -> IO [V.Vector B.ByteString]
226+
go :: B.ByteString -> [V.Vector (Maybe B.ByteString)] -> IO [V.Vector (Maybe B.ByteString)]
226227
go str acc = case pushChunk decoder str of
227228
BG.Done rest _ v -> do
228229
when (msgFilter v) $ writeChan allChan v

src/Database/PostgreSQL/Driver/Query.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ import Database.PostgreSQL.Driver.StatementStorage
1616
-- Public
1717
data Query = Query
1818
{ qStatement :: B.ByteString
19-
, qValues :: V.Vector (Oid, B.ByteString)
19+
, qValues :: V.Vector (Oid, Maybe B.ByteString)
2020
, qParamsFormat :: Format
2121
, qResultFormat :: Format
2222
, qCachePolicy :: CachePolicy

src/Database/PostgreSQL/Protocol/Decoders.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -73,9 +73,9 @@ decodeServerMessage = do
7373

7474
-- | Decodes a single data value. Length `-1` indicates a NULL column value.
7575
-- No value bytes follow in the NULL case.
76-
decodeValue :: Get B.ByteString
76+
decodeValue :: Get (Maybe B.ByteString)
7777
decodeValue = fromIntegral <$> getInt32be >>= \n ->
78-
if n == -1 then pure "" else getByteString n
78+
if n == -1 then pure Nothing else Just <$> getByteString n
7979

8080
decodeTransactionStatus :: Get TransactionStatus
8181
decodeTransactionStatus = getWord8 >>= \t ->

src/Database/PostgreSQL/Protocol/Encoders.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -74,9 +74,9 @@ encodeClientMessage Terminate
7474

7575
-- Encodes single data values. Length `-1` indicates a NULL parameter value.
7676
-- No value bytes follow in the NULL case.
77-
encodeValue :: B.ByteString -> Encode
78-
encodeValue v | B.null v = putInt32BE (-1)
79-
| otherwise = putInt32BE (fromIntegral $ B.length v)
77+
encodeValue :: Maybe B.ByteString -> Encode
78+
encodeValue Nothing = putInt32BE (-1)
79+
encodeValue (Just v) = putInt32BE (fromIntegral $ B.length v)
8080
<> putByteString v
8181

8282
encodeFormat :: Format -> Encode

src/Database/PostgreSQL/Protocol/Types.hs

Lines changed: 5 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -65,12 +65,7 @@ data CommandResult
6565
-- 9.6.0 ServerVersion 9 6 0 ""
6666
-- 10.1beta2 - ServerVersion 10 1 0 "beta2"
6767
data ServerVersion = ServerVersion Word8 Word8 Word8 ByteString
68-
deriving (Eq)
69-
70-
instance Show ServerVersion where
71-
show (ServerVersion major minor revision desc) =
72-
"v" ++ show major ++ "." ++ show minor ++ "." ++ show revision
73-
++ if B.null desc then "" else show desc
68+
deriving (Eq, Show)
7469

7570
data TransactionStatus
7671
-- | not in a transaction block
@@ -106,9 +101,9 @@ data AuthResponse
106101

107102
data ClientMessage
108103
= Bind !PortalName !StatementName
109-
!Format -- parameter format code, one format for all
110-
!(Vector ByteString) -- the values of parameters, the empty string
111-
-- is recognized as NULL
104+
!Format -- parameter format code, one format for all
105+
!(Vector (Maybe ByteString)) -- the values of parameters, Nothing
106+
-- is recognized as NULL
112107
!Format -- to apply code to all result columns
113108
-- Postgres use one command `close` for closing both statements and
114109
-- portals, but we distinguish them
@@ -136,8 +131,7 @@ data ServerMessage
136131
| BindComplete
137132
| CloseComplete
138133
| CommandComplete CommandResult
139-
| DataRow (Vector ByteString) -- an empty string should be recognized
140-
-- as NULL
134+
| DataRow (Vector (Maybe ByteString)) -- Nothing shoulde be recognized as NULL
141135
| EmptyQueryResponse
142136
| ErrorResponse ErrorDesc
143137
| NoData

tests/Driver.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@ module Driver where
33
import Data.Monoid ((<>))
44
import Data.Foldable
55
import Control.Monad
6+
import Data.Maybe
67
import Data.Either
78
import qualified Data.ByteString as B
89
import qualified Data.ByteString.Char8 as BS
@@ -35,19 +36,19 @@ testDriver = testGroup "Driver"
3536
]
3637

3738
makeQuery1 :: B.ByteString -> Query
38-
makeQuery1 n = Query "SELECT $1" (V.fromList [(Oid 23, n)])
39+
makeQuery1 n = Query "SELECT $1" (V.fromList [(Oid 23, Just n)])
3940
Text Text AlwaysCache
4041

4142
makeQuery2 :: B.ByteString -> B.ByteString -> Query
4243
makeQuery2 n1 n2 = Query "SELECT $1 + $2"
43-
(V.fromList [(Oid 23, n1), (Oid 23, n2)]) Text Text AlwaysCache
44+
(V.fromList [(Oid 23, Just n1), (Oid 23, Just n2)]) Text Text AlwaysCache
4445

4546
fromRight :: Either e a -> a
4647
fromRight (Right v) = v
4748
fromRight _ = error "fromRight"
4849

4950
fromMessage :: Either e DataMessage -> B.ByteString
50-
fromMessage (Right (DataMessage [v])) = V.head v
51+
fromMessage (Right (DataMessage [v])) = fromJust $ V.head v
5152
fromMessage _ = error "from message"
5253

5354
-- | Single batch.
@@ -129,8 +130,8 @@ checkInvalidResult conn n = readNextData conn >>=
129130
testInvalidBatch :: IO ()
130131
testInvalidBatch = do
131132
let rightQuery = makeQuery1 "5"
132-
q1 = Query "SEL $1" (V.fromList [(Oid 23, "5")]) Text Text NeverCache
133-
q2 = Query "SELECT $1" (V.fromList [(Oid 23, "a")]) Text Text NeverCache
133+
q1 = Query "SEL $1" (V.fromList [(Oid 23, Just "5")]) Text Text NeverCache
134+
q2 = Query "SELECT $1" (V.fromList [(Oid 23, Just "a")]) Text Text NeverCache
134135
q4 = Query "SELECT $1" (V.fromList []) Text Text NeverCache
135136

136137
assertInvalidBatch "Parse error" [q1]

tests/Protocol.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,7 +50,7 @@ testExtendedQuery = withConnectionAll $ \c -> do
5050
statement = StatementSQL "SELECT $1 + $2"
5151
sendMessage rawConn $ Parse sname statement (V.fromList [Oid 23, Oid 23])
5252
sendMessage rawConn $
53-
Bind pname sname Text (V.fromList ["1", "2"]) Text
53+
Bind pname sname Text (V.fromList [Just "1", Just "2"]) Text
5454
sendMessage rawConn $ Execute pname noLimitToReceive
5555
sendMessage rawConn $ DescribeStatement sname
5656
sendMessage rawConn $ DescribePortal pname

0 commit comments

Comments
 (0)
0