hasql/library/Hasql/Private/IO.hs

168 lines
6.0 KiB
Haskell
Raw Normal View History

2015-12-21 16:11:14 +03:00
-- |
-- An API of low-level IO operations.
module Hasql.Private.IO
where
import Hasql.Private.Prelude
import Hasql.Private.Errors
2015-12-21 16:11:14 +03:00
import qualified Database.PostgreSQL.LibPQ as LibPQ
import qualified Hasql.Private.Commands as Commands
2015-12-21 16:11:14 +03:00
import qualified Hasql.Private.PreparedStatementRegistry as PreparedStatementRegistry
import qualified Hasql.Private.Decoders.Result as ResultDecoders
import qualified Hasql.Private.Decoders.Results as ResultsDecoders
import qualified Hasql.Private.Encoders.Params as ParamsEncoders
2015-12-21 16:11:14 +03:00
import qualified Data.DList as DList
{-# INLINE acquireConnection #-}
acquireConnection :: ByteString -> IO LibPQ.Connection
acquireConnection =
LibPQ.connectdb
{-# INLINE acquirePreparedStatementRegistry #-}
acquirePreparedStatementRegistry :: IO PreparedStatementRegistry.PreparedStatementRegistry
acquirePreparedStatementRegistry =
PreparedStatementRegistry.new
{-# INLINE releaseConnection #-}
releaseConnection :: LibPQ.Connection -> IO ()
releaseConnection connection =
LibPQ.finish connection
{-# INLINE checkConnectionStatus #-}
checkConnectionStatus :: LibPQ.Connection -> IO (Maybe (Maybe ByteString))
checkConnectionStatus c =
do
s <- LibPQ.status c
case s of
LibPQ.ConnectionOk -> return Nothing
_ -> fmap Just (LibPQ.errorMessage c)
{-# INLINE checkServerVersion #-}
checkServerVersion :: LibPQ.Connection -> IO (Maybe Int)
checkServerVersion c =
fmap (mfilter (< 80200) . Just) (LibPQ.serverVersion c)
{-# INLINE getIntegerDatetimes #-}
getIntegerDatetimes :: LibPQ.Connection -> IO Bool
getIntegerDatetimes c =
fmap decodeValue $ LibPQ.parameterStatus c "integer_datetimes"
where
decodeValue =
\case
Just "on" -> True
_ -> False
{-# INLINE initConnection #-}
initConnection :: LibPQ.Connection -> IO ()
initConnection c =
void $ LibPQ.exec c (Commands.asBytes (Commands.setEncodersToUTF8 <> Commands.setMinClientMessagesToWarning))
{-# INLINE getResults #-}
getResults :: LibPQ.Connection -> Bool -> ResultsDecoders.Results a -> IO (Either CommandError a)
2016-01-24 19:52:33 +03:00
getResults connection integerDatetimes decoder =
2015-12-21 16:11:14 +03:00
{-# SCC "getResults" #-}
2016-01-24 19:52:33 +03:00
(<*) <$> get <*> dropRemainders
where
get =
ResultsDecoders.run decoder (integerDatetimes, connection)
dropRemainders =
ResultsDecoders.run ResultsDecoders.dropRemainders (integerDatetimes, connection)
2015-12-21 16:11:14 +03:00
{-# INLINE getPreparedStatementKey #-}
getPreparedStatementKey ::
LibPQ.Connection -> PreparedStatementRegistry.PreparedStatementRegistry ->
ByteString -> [LibPQ.Oid] ->
IO (Either CommandError ByteString)
2015-12-21 16:11:14 +03:00
getPreparedStatementKey connection registry template oidList =
{-# SCC "getPreparedStatementKey" #-}
PreparedStatementRegistry.update localKey onNewRemoteKey onOldRemoteKey registry
2015-12-21 16:11:14 +03:00
where
localKey =
PreparedStatementRegistry.LocalKey template wordOIDList
where
wordOIDList =
map (\(LibPQ.Oid x) -> fromIntegral x) oidList
onNewRemoteKey key =
do
sent <- LibPQ.sendPrepare connection key template (mfilter (not . null) (Just oidList))
let resultsDecoder =
if sent
2019-05-21 13:25:22 +03:00
then ResultsDecoders.single ResultDecoders.noResult
else ResultsDecoders.clientError
fmap resultsMapping $ getResults connection undefined resultsDecoder
where
resultsMapping =
\case
Left x -> (False, Left x)
Right _ -> (True, Right key)
onOldRemoteKey key =
pure (pure key)
2015-12-21 16:11:14 +03:00
{-# INLINE checkedSend #-}
checkedSend :: LibPQ.Connection -> IO Bool -> IO (Either CommandError ())
2015-12-21 16:11:14 +03:00
checkedSend connection send =
send >>= \case
False -> fmap (Left . ClientError) $ LibPQ.errorMessage connection
2015-12-21 16:11:14 +03:00
True -> pure (Right ())
2018-05-23 13:33:34 +03:00
{-# INLINE sendPreparedParametricStatement #-}
sendPreparedParametricStatement ::
2015-12-21 16:11:14 +03:00
LibPQ.Connection ->
PreparedStatementRegistry.PreparedStatementRegistry ->
Bool ->
2015-12-21 16:11:14 +03:00
ByteString ->
ParamsEncoders.Params a ->
a ->
IO (Either CommandError ())
2018-05-23 13:33:34 +03:00
sendPreparedParametricStatement connection registry integerDatetimes template (ParamsEncoders.Params (Op encoderOp)) input =
let
(oidList, valueAndFormatList) =
let
step (oid, format, encoder, _) ~(oidList, bytesAndFormatList) =
(,)
(oid : oidList)
(fmap (\bytes -> (bytes, format)) (encoder integerDatetimes) : bytesAndFormatList)
in foldr step ([], []) (encoderOp input)
in runExceptT $ do
key <- ExceptT $ getPreparedStatementKey connection registry template oidList
ExceptT $ checkedSend connection $ LibPQ.sendQueryPrepared connection key valueAndFormatList LibPQ.Binary
2015-12-21 16:11:14 +03:00
2018-05-23 13:33:34 +03:00
{-# INLINE sendUnpreparedParametricStatement #-}
sendUnpreparedParametricStatement ::
2015-12-21 16:11:14 +03:00
LibPQ.Connection ->
Bool ->
2015-12-21 16:11:14 +03:00
ByteString ->
ParamsEncoders.Params a ->
a ->
IO (Either CommandError ())
2018-05-23 13:33:34 +03:00
sendUnpreparedParametricStatement connection integerDatetimes template (ParamsEncoders.Params (Op encoderOp)) input =
let
params =
let
step (oid, format, encoder, _) acc =
((,,) <$> pure oid <*> encoder integerDatetimes <*> pure format) : acc
in foldr step [] (encoderOp input)
in checkedSend connection $ LibPQ.sendQueryParams connection template params LibPQ.Binary
2015-12-21 16:11:14 +03:00
2018-05-23 13:33:34 +03:00
{-# INLINE sendParametricStatement #-}
sendParametricStatement ::
2015-12-21 16:11:14 +03:00
LibPQ.Connection ->
Bool ->
PreparedStatementRegistry.PreparedStatementRegistry ->
ByteString ->
ParamsEncoders.Params a ->
Bool ->
a ->
IO (Either CommandError ())
2018-05-23 13:33:34 +03:00
sendParametricStatement connection integerDatetimes registry template encoder prepared params =
{-# SCC "sendParametricStatement" #-}
2015-12-21 16:11:14 +03:00
if prepared
2018-05-23 13:33:34 +03:00
then sendPreparedParametricStatement connection registry integerDatetimes template encoder params
else sendUnpreparedParametricStatement connection integerDatetimes template encoder params
2015-12-21 16:11:14 +03:00
2018-05-23 13:33:34 +03:00
{-# INLINE sendNonparametricStatement #-}
sendNonparametricStatement :: LibPQ.Connection -> ByteString -> IO (Either CommandError ())
sendNonparametricStatement connection sql =
2015-12-21 16:11:14 +03:00
checkedSend connection $ LibPQ.sendQuery connection sql