51 lines
1.2 KiB
Haskell

{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedRecordDot #-}
module Database.PostgreSQL.Opium.Connection
( Connection
, unsafeWithRawConnection
, withRawConnection
, connect
, close
) where
import Control.Concurrent.MVar (MVar, newMVar, modifyMVar_, withMVar)
import Data.ByteString (ByteString)
import GHC.Stack (HasCallStack)
import qualified Database.PostgreSQL.LibPQ as LibPQ
newtype Connection = Connection
{ rawConnection :: MVar (Maybe LibPQ.Connection)
}
withRawConnection
:: HasCallStack
=> (Maybe LibPQ.Connection -> IO a)
-> Connection
-> IO a
withRawConnection f conn = withMVar conn.rawConnection f
unsafeWithRawConnection
:: HasCallStack
=> (LibPQ.Connection -> IO a)
-> Connection
-> IO 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
Connection <$> newMVar (Just rawConn)
close :: Connection -> IO ()
close conn = modifyMVar_ conn.rawConnection $ \case
Just rawConn -> do
LibPQ.finish rawConn
pure Nothing
Nothing ->
pure Nothing