@@ -12,13 +12,12 @@ module Database.PostgreSQL.Driver.Query
1212 , collectUntilReadyForQuery
1313 ) where
1414
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
2015import 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 )
2221
2322import Database.PostgreSQL.Protocol.Encoders
2423import Database.PostgreSQL.Protocol.Store.Encode
@@ -31,26 +30,30 @@ import Database.PostgreSQL.Driver.StatementStorage
3130
3231-- Public
3332data 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
3938 } deriving (Show )
4039
4140-- | Public
41+ {- INLINE sendBatchAndFlush #-}
4242sendBatchAndFlush :: Connection -> [Query ] -> IO ()
4343sendBatchAndFlush = sendBatchEndBy Flush
4444
4545-- | Public
46+ {-# INLINE sendBatchAndSync #-}
4647sendBatchAndSync :: Connection -> [Query ] -> IO ()
4748sendBatchAndSync = sendBatchEndBy Sync
4849
4950-- | Public
51+ {-# INLINE sendSync #-}
5052sendSync :: Connection -> IO ()
5153sendSync conn = sendEncode conn $ encodeClientMessage Sync
5254
5355-- | Public
56+ {-# INLINABLE readNextData #-}
5457readNextData :: Connection -> IO (Either Error DataRows )
5558readNextData conn =
5659 readChan (connOutChan conn) >>=
@@ -62,6 +65,7 @@ readNextData conn =
6265 DataReady -> throwIncorrectUsage
6366 " Expected DataRow message, but got ReadyForQuery"
6467
68+ {-# INLINABLE waitReadyForQuery #-}
6569waitReadyForQuery :: Connection -> IO (Either Error () )
6670waitReadyForQuery conn =
6771 readChan (connOutChan conn) >>=
@@ -77,6 +81,7 @@ waitReadyForQuery conn =
7781 DataReady -> pure $ Right ()
7882
7983-- Helper
84+ {-# INLINE sendBatchEndBy #-}
8085sendBatchEndBy :: ClientMessage -> Connection -> [Query ] -> IO ()
8186sendBatchEndBy msg conn qs = do
8287 batch <- constructBatch conn qs
@@ -90,28 +95,27 @@ constructBatch conn = fmap fold . traverse constructSingle
9095 pname = PortalName " "
9196 constructSingle q = do
9297 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)
108112 (qResultFormat q)
109113 executeMessage = encodeClientMessage $
110114 Execute pname noLimitToReceive
111115 pure $ parseMessage <> bindMessage <> executeMessage
112116
113117-- | Public
114- sendSimpleQuery :: ConnectionCommon -> B. ByteString -> IO (Either Error () )
118+ sendSimpleQuery :: ConnectionCommon -> ByteString -> IO (Either Error () )
115119sendSimpleQuery conn q = do
116120 sendMessage (connRawConnection conn) $ SimpleQuery (StatementSQL q)
117121 (checkErrors =<< ) <$> collectUntilReadyForQuery conn
@@ -122,8 +126,8 @@ sendSimpleQuery conn q = do
122126-- | Public
123127describeStatement
124128 :: ConnectionCommon
125- -> B. ByteString
126- -> IO (Either Error (V. Vector Oid , V. Vector FieldDescription ))
129+ -> ByteString
130+ -> IO (Either Error (Vector Oid , Vector FieldDescription ))
127131describeStatement conn stmt = do
128132 sendEncode conn $
129133 encodeClientMessage (Parse sname (StatementSQL stmt) [] )
@@ -135,7 +139,7 @@ describeStatement conn stmt = do
135139 sname = StatementName " "
136140 parseMessages msgs = case msgs of
137141 [ParameterDescription params, NoData ]
138- -> pure $ Right (params, V. empty )
142+ -> pure $ Right (params, mempty )
139143 [ParameterDescription params, RowDescription fields]
140144 -> pure $ Right (params, fields)
141145 xs -> maybe
@@ -160,5 +164,6 @@ findFirstError [] = Nothing
160164findFirstError (ErrorResponse desc : _) = Just desc
161165findFirstError (_ : xs) = findFirstError xs
162166
167+ {-# INLINE readChan #-}
163168readChan :: TQueue a -> IO a
164169readChan = atomically . readTQueue
0 commit comments