40 lines
979 B
Haskell

{-# LANGUAGE LambdaCase #-}
module Database.PostgreSQL.Opium.Connection
( Connection
, unsafeWithRawConnection
, withRawConnection
, connect
, close
) where
import Data.ByteString (ByteString)
import GHC.Stack (HasCallStack)
import qualified Database.PostgreSQL.LibPQ as LibPQ
newtype Connection = Connection LibPQ.Connection
withRawConnection
:: (Maybe LibPQ.Connection -> m a)
-> Connection
-> m a
withRawConnection f (Connection rawConn) = f (Just rawConn)
unsafeWithRawConnection
:: HasCallStack
=> (LibPQ.Connection -> m a)
-> Connection
-> m a
unsafeWithRawConnection f = withRawConnection $ \case
Nothing -> error "raw connection is missing! perhaps the connection was already closed."
Just rawConn -> f rawConn
connect :: ByteString -> IO Connection
connect connectionString = do
rawConn <- LibPQ.connectdb connectionString
pure $ Connection rawConn
close :: Connection -> IO ()
close (Connection rawConn) = LibPQ.finish rawConn