@@ -12,13 +12,12 @@ module Database.PostgreSQL.Driver.Query
12
12
, collectUntilReadyForQuery
13
13
) where
14
14
15
- import Data.Foldable
16
- import Data.Monoid
17
- import Data.Bifunctor
18
- import qualified Data.Vector as V
19
- import qualified Data.ByteString as B
20
15
import Control.Concurrent.STM.TQueue (TQueue , readTQueue )
21
- import Control.Concurrent.STM (atomically )
16
+ import Control.Concurrent.STM (atomically )
17
+ import Data.Foldable (fold )
18
+ import Data.Monoid ((<>) )
19
+ import Data.ByteString (ByteString )
20
+ import Data.Vector (Vector )
22
21
23
22
import Database.PostgreSQL.Protocol.Encoders
24
23
import Database.PostgreSQL.Protocol.Store.Encode
@@ -31,26 +30,30 @@ import Database.PostgreSQL.Driver.StatementStorage
31
30
32
31
-- Public
33
32
data Query = Query
34
- { qStatement :: B. ByteString
35
- , qValues :: [(Oid , Maybe Encode )]
36
- , qParamsFormat :: Format
37
- , qResultFormat :: Format
38
- , qCachePolicy :: CachePolicy
33
+ { qStatement :: ! ByteString
34
+ , qValues :: ! [(Oid , Maybe Encode )]
35
+ , qParamsFormat :: ! Format
36
+ , qResultFormat :: ! Format
37
+ , qCachePolicy :: ! CachePolicy
39
38
} deriving (Show )
40
39
41
40
-- | Public
41
+ {- INLINE sendBatchAndFlush #-}
42
42
sendBatchAndFlush :: Connection -> [Query ] -> IO ()
43
43
sendBatchAndFlush = sendBatchEndBy Flush
44
44
45
45
-- | Public
46
+ {-# INLINE sendBatchAndSync #-}
46
47
sendBatchAndSync :: Connection -> [Query ] -> IO ()
47
48
sendBatchAndSync = sendBatchEndBy Sync
48
49
49
50
-- | Public
51
+ {-# INLINE sendSync #-}
50
52
sendSync :: Connection -> IO ()
51
53
sendSync conn = sendEncode conn $ encodeClientMessage Sync
52
54
53
55
-- | Public
56
+ {-# INLINABLE readNextData #-}
54
57
readNextData :: Connection -> IO (Either Error DataRows )
55
58
readNextData conn =
56
59
readChan (connOutChan conn) >>=
@@ -62,6 +65,7 @@ readNextData conn =
62
65
DataReady -> throwIncorrectUsage
63
66
" Expected DataRow message, but got ReadyForQuery"
64
67
68
+ {-# INLINABLE waitReadyForQuery #-}
65
69
waitReadyForQuery :: Connection -> IO (Either Error () )
66
70
waitReadyForQuery conn =
67
71
readChan (connOutChan conn) >>=
@@ -77,6 +81,7 @@ waitReadyForQuery conn =
77
81
DataReady -> pure $ Right ()
78
82
79
83
-- Helper
84
+ {-# INLINE sendBatchEndBy #-}
80
85
sendBatchEndBy :: ClientMessage -> Connection -> [Query ] -> IO ()
81
86
sendBatchEndBy msg conn qs = do
82
87
batch <- constructBatch conn qs
@@ -90,28 +95,27 @@ constructBatch conn = fmap fold . traverse constructSingle
90
95
pname = PortalName " "
91
96
constructSingle q = do
92
97
let stmtSQL = StatementSQL $ qStatement q
93
- (sname, parseMessage) <- case qCachePolicy q of
94
- AlwaysCache -> do
95
- mName <- lookupStatement storage stmtSQL
96
- case mName of
97
- Nothing -> do
98
- newName <- storeStatement storage stmtSQL
99
- pure (newName, encodeClientMessage $
100
- Parse newName stmtSQL (fst <$> qValues q))
101
- Just name -> pure (name, mempty )
102
- NeverCache -> do
103
- let newName = defaultStatementName
104
- pure (newName, encodeClientMessage $
105
- Parse newName stmtSQL (fst <$> qValues q))
106
- let bindMessage = encodeClientMessage $
107
- Bind pname sname (qParamsFormat q) (snd <$> qValues q)
98
+ (stmtName, needParse) <- case qCachePolicy q of
99
+ AlwaysCache -> lookupStatement storage stmtSQL >>= \ case
100
+ Nothing -> do
101
+ newName <- storeStatement storage stmtSQL
102
+ pure (newName, True )
103
+ Just name ->
104
+ pure (name, False )
105
+ NeverCache -> pure (defaultStatementName, True )
106
+ let parseMessage = if needParse
107
+ then encodeClientMessage $
108
+ Parse stmtName stmtSQL (fst <$> qValues q)
109
+ else mempty
110
+ bindMessage = encodeClientMessage $
111
+ Bind pname stmtName (qParamsFormat q) (snd <$> qValues q)
108
112
(qResultFormat q)
109
113
executeMessage = encodeClientMessage $
110
114
Execute pname noLimitToReceive
111
115
pure $ parseMessage <> bindMessage <> executeMessage
112
116
113
117
-- | Public
114
- sendSimpleQuery :: ConnectionCommon -> B. ByteString -> IO (Either Error () )
118
+ sendSimpleQuery :: ConnectionCommon -> ByteString -> IO (Either Error () )
115
119
sendSimpleQuery conn q = do
116
120
sendMessage (connRawConnection conn) $ SimpleQuery (StatementSQL q)
117
121
(checkErrors =<< ) <$> collectUntilReadyForQuery conn
@@ -122,8 +126,8 @@ sendSimpleQuery conn q = do
122
126
-- | Public
123
127
describeStatement
124
128
:: ConnectionCommon
125
- -> B. ByteString
126
- -> IO (Either Error (V. Vector Oid , V. Vector FieldDescription ))
129
+ -> ByteString
130
+ -> IO (Either Error (Vector Oid , Vector FieldDescription ))
127
131
describeStatement conn stmt = do
128
132
sendEncode conn $
129
133
encodeClientMessage (Parse sname (StatementSQL stmt) [] )
@@ -135,7 +139,7 @@ describeStatement conn stmt = do
135
139
sname = StatementName " "
136
140
parseMessages msgs = case msgs of
137
141
[ParameterDescription params, NoData ]
138
- -> pure $ Right (params, V. empty )
142
+ -> pure $ Right (params, mempty )
139
143
[ParameterDescription params, RowDescription fields]
140
144
-> pure $ Right (params, fields)
141
145
xs -> maybe
@@ -160,5 +164,6 @@ findFirstError [] = Nothing
160
164
findFirstError (ErrorResponse desc : _) = Just desc
161
165
findFirstError (_ : xs) = findFirstError xs
162
166
167
+ {-# INLINE readChan #-}
163
168
readChan :: TQueue a -> IO a
164
169
readChan = atomically . readTQueue
0 commit comments