module Test.Database.Hasql
(
startupPostgres
, startupPostgresInit
, teardownPostgres
, allocateConnection
, freeConnection
, InitException(..)
, explain
) where
import Control.Exception
import Control.Monad.IO.Class
import Data.ByteString (ByteString)
import Data.Profunctor
import Data.Typeable
import Database.Postgres.Temp qualified as Temp
import Hasql.Connection qualified as HC
import Hasql.Decoders qualified as HD
import Hasql.Session qualified as HS
import Hasql.Statement qualified as HST
import Test.QuickCheck
import Test.Hspec
explain
:: (Arbitrary input)
=> HST.Statement input output
-> HC.Connection
-> Expectation
explain :: Statement input output -> Connection -> Expectation
explain Statement input output
t Connection
c = do
let t' :: Statement input ()
t' = case Statement input output
t of
HST.Statement ByteString
sql Params input
enc Result output
_dec Bool
_ -> ByteString
-> Params input -> Result () -> Bool -> Statement input ()
forall a b.
ByteString -> Params a -> Result b -> Bool -> Statement a b
HST.Statement (ByteString
"EXPLAIN " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
sql) Params input
enc Result ()
HD.noResult Bool
False
input
input <- IO input -> IO input
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO input -> IO input) -> IO input -> IO input
forall a b. (a -> b) -> a -> b
$ Gen input -> IO input
forall a. Gen a -> IO a
generate (Gen input -> IO input) -> Gen input -> IO input
forall a b. (a -> b) -> a -> b
$ Int -> Gen input -> Gen input
forall a. Int -> Gen a -> Gen a
resize Int
2 (Gen input -> Gen input) -> Gen input -> Gen input
forall a b. (a -> b) -> a -> b
$ Gen input
forall a. Arbitrary a => Gen a
arbitrary
Session () -> Connection -> IO (Either QueryError ())
forall a. Session a -> Connection -> IO (Either QueryError a)
HS.run (input -> Statement input () -> Session ()
forall params result.
params -> Statement params result -> Session result
HS.statement input
input Statement input ()
t') Connection
c IO (Either QueryError ()) -> Either QueryError () -> Expectation
forall a. (HasCallStack, Show a, Eq a) => IO a -> a -> Expectation
`shouldReturn` () -> Either QueryError ()
forall a b. b -> Either a b
Right ()
data InitException
= InitException HS.QueryError
| ConnectException HC.ConnectionError
| PostgresStartException Temp.StartError
deriving (Int -> InitException -> ShowS
[InitException] -> ShowS
InitException -> String
(Int -> InitException -> ShowS)
-> (InitException -> String)
-> ([InitException] -> ShowS)
-> Show InitException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [InitException] -> ShowS
$cshowList :: [InitException] -> ShowS
show :: InitException -> String
$cshow :: InitException -> String
showsPrec :: Int -> InitException -> ShowS
$cshowsPrec :: Int -> InitException -> ShowS
Show, Typeable)
instance Exception InitException
startupPostgres :: ByteString -> IO Temp.DB
startupPostgres :: ByteString -> IO DB
startupPostgres ByteString
init_script = (Connection -> Expectation) -> IO DB
startupPostgresInit Connection -> Expectation
script where
script :: Connection -> Expectation
script Connection
c = do
Session () -> Connection -> IO (Either QueryError ())
forall a. Session a -> Connection -> IO (Either QueryError a)
HS.run (ByteString -> Session ()
HS.sql ByteString
init_script ) Connection
c IO (Either QueryError ())
-> (Either QueryError () -> Expectation) -> Expectation
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Right {} -> () -> Expectation
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Left QueryError
e -> InitException -> Expectation
forall e a. Exception e => e -> IO a
throwIO (InitException -> Expectation) -> InitException -> Expectation
forall a b. (a -> b) -> a -> b
$ QueryError -> InitException
InitException QueryError
e
startupPostgresInit :: (HC.Connection -> IO ()) -> IO Temp.DB
startupPostgresInit :: (Connection -> Expectation) -> IO DB
startupPostgresInit Connection -> Expectation
run_init = do
IO (Either StartError DB)
Temp.start IO (Either StartError DB)
-> (Either StartError DB -> IO DB) -> IO DB
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left StartError
e -> InitException -> IO DB
forall e a. Exception e => e -> IO a
throwIO (InitException -> IO DB) -> InitException -> IO DB
forall a b. (a -> b) -> a -> b
$ StartError -> InitException
PostgresStartException StartError
e
Right DB
db -> do
Connection
c <- ByteString -> IO (Either ConnectionError Connection)
HC.acquire (DB -> ByteString
Temp.toConnectionString DB
db) IO (Either ConnectionError Connection)
-> (Either ConnectionError Connection -> IO Connection)
-> IO Connection
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left ConnectionError
e -> InitException -> IO Connection
forall e a. Exception e => e -> IO a
throwIO (InitException -> IO Connection) -> InitException -> IO Connection
forall a b. (a -> b) -> a -> b
$ ConnectionError -> InitException
ConnectException ConnectionError
e
Right Connection
c -> Connection -> IO Connection
forall (f :: * -> *) a. Applicative f => a -> f a
pure Connection
c
Connection -> Expectation
run_init Connection
c
DB -> IO DB
forall (f :: * -> *) a. Applicative f => a -> f a
pure DB
db
teardownPostgres :: Temp.DB -> IO ()
teardownPostgres :: DB -> Expectation
teardownPostgres = DB -> Expectation
Temp.stop
allocateConnection :: Temp.DB -> IO HC.Connection
allocateConnection :: DB -> IO Connection
allocateConnection DB
db = ByteString -> IO (Either ConnectionError Connection)
HC.acquire (DB -> ByteString
Temp.toConnectionString DB
db) IO (Either ConnectionError Connection)
-> (Either ConnectionError Connection -> IO Connection)
-> IO Connection
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Left ConnectionError
e -> InitException -> IO Connection
forall e a. Exception e => e -> IO a
throwIO (InitException -> IO Connection) -> InitException -> IO Connection
forall a b. (a -> b) -> a -> b
$ ConnectionError -> InitException
ConnectException ConnectionError
e
Right Connection
conn -> Connection -> IO Connection
forall (f :: * -> *) a. Applicative f => a -> f a
pure Connection
conn
freeConnection :: HC.Connection -> IO ()
freeConnection :: Connection -> Expectation
freeConnection = Connection -> Expectation
HC.release