]> git.immae.eu Git - github/fretlink/squeal-hspec.git/blame - src/Squeal/PostgreSQL/Hspec.hs
Merge pull request #4 from adfretlink/bump-lts
[github/fretlink/squeal-hspec.git] / src / Squeal / PostgreSQL / Hspec.hs
CommitLineData
aa94c1a5
R
1{-|
2Helpers for creating database tests with hspec and squeal, inspired by Jonathan Fischoff's
3[hspec-pg-transact](http://hackage.haskell.org/package/hspec-pg-transact).
4
5This uses @tmp-postgres@ to automatically and connect to a temporary instance of postgres on a random port.
6
7Tests can be written with 'itDB' which is wrapper around 'it' that uses the passed in 'TestDB' to run a db transaction automatically for the test.
8
9The libary also provides a few other functions for more fine grained control over running transactions in tests.
10-}
11{-# LANGUAGE DataKinds #-}
12{-# LANGUAGE FlexibleContexts #-}
aa94c1a5
R
13{-# LANGUAGE MonoLocalBinds #-}
14{-# LANGUAGE RankNTypes #-}
15{-# LANGUAGE RecordWildCards #-}
dd35032c 16{-# LANGUAGE TupleSections #-}
aa94c1a5
R
17{-# LANGUAGE TypeInType #-}
18{-# LANGUAGE TypeOperators #-}
19module Squeal.PostgreSQL.Hspec
20where
21
22import Control.Exception
23import Control.Monad
d8e546eb 24import Control.Monad.Base (liftBase)
dd35032c 25import Data.ByteString (ByteString)
d8e546eb 26import qualified Data.ByteString.Char8 as BSC
cfe36707 27import Database.Postgres.Temp as Temp
aa94c1a5 28import Squeal.PostgreSQL
dd35032c 29import System.Environment (lookupEnv)
aa94c1a5
R
30import Test.Hspec
31
32data TestDB a = TestDB
dd35032c 33 { tempDB :: Maybe Temp.DB
aa94c1a5 34 -- ^ Handle for temporary @postgres@ process
4c2683dd 35 , pool :: Pool (K Connection a)
aa94c1a5 36 -- ^ Pool of 50 connections to the temporary @postgres@
dd35032c 37 , connectionString :: ByteString
aa94c1a5
R
38 }
39
4c2683dd
AD
40type Fixtures db a = (Pool (K Connection db) -> IO a)
41type Actions db a = PQ db db IO a
42type FixtureContext db fix = (TestDB db, fix)
43type Migrations def from to = Path (Migration def) from to
aa94c1a5 44
dd35032c
R
45testDBEnv :: String
46testDBEnv = "TEST_DB_CONNECTION_STRING"
47
48getOrCreateConnectionString :: IO (ByteString, Maybe Temp.DB)
49getOrCreateConnectionString = do
50 hasConnectionString <- lookupEnv testDBEnv
51 maybe createTempDB (pure . (, Nothing) . BSC.pack) hasConnectionString
52
53createTempDB :: IO (ByteString, Maybe Temp.DB)
54createTempDB = do
cfe36707
AD
55 tempDB <- either throwIO return =<< Temp.start
56 let connectionString = Temp.toConnectionString tempDB
dd35032c
R
57 pure (connectionString, Just tempDB)
58
aa94c1a5
R
59-- | Start a temporary @postgres@ process and create a pool of connections to it
60setupDB
4c2683dd
AD
61 :: Migratory def (IsoQ (Indexed PQ IO ()))
62 => Migrations def schema0 schema
b47ba97b
AD
63 -> Fixtures schema fix
64 -> IO (FixtureContext schema fix)
aa94c1a5 65setupDB migration fixtures = do
dd35032c
R
66 (connectionString, tempDB) <- getOrCreateConnectionString
67 BSC.putStrLn connectionString
aa94c1a5
R
68 let singleStripe = 1
69 keepConnectionForOneHour = 3600
70 poolSizeOfFifty = 50
71 pool <- createConnectionPool
72 connectionString
73 singleStripe
74 keepConnectionForOneHour
75 poolSizeOfFifty
d8e546eb 76 withConnection connectionString (migrateUp migration)
b47ba97b
AD
77 res <- fixtures pool
78 pure (TestDB {..}, res)
aa94c1a5
R
79
80-- | Drop all the connections and shutdown the @postgres@ process
dd35032c 81teardownDB
4c2683dd
AD
82 :: Migratory def (IsoQ (Indexed PQ IO ()))
83 => Migrations def schema0 schema
dd35032c
R
84 -> TestDB a
85 -> IO ()
86teardownDB migration TestDB {..} = do
87 withConnection connectionString (migrateDown migration)
4c2683dd 88 destroyConnectionPool pool
dd35032c 89 maybe (pure ()) (void . Temp.stop) tempDB
aa94c1a5
R
90
91-- | Run an 'IO' action with a connection from the pool
4c2683dd
AD
92withPool :: TestDB db -> Actions db a -> IO a
93withPool testDB = liftBase . usingConnectionPool (pool testDB)
aa94c1a5
R
94
95-- | Run an 'DB' transaction, using 'transactionally_'
4c2683dd 96withDB :: Actions db a -> TestDB db -> IO a
aa94c1a5 97withDB action testDB =
4c2683dd 98 usingConnectionPool (pool testDB) (transactionally_ action)
aa94c1a5
R
99
100-- | Flipped version of 'withDB'
4c2683dd 101runDB :: TestDB db -> Actions db a -> IO a
aa94c1a5
R
102runDB = flip withDB
103
4c2683dd 104withFixture :: (fix -> Actions db a) -> FixtureContext db fix -> IO a
b47ba97b 105withFixture action (db, fix) =
4c2683dd 106 usingConnectionPool (pool db) (transactionally_ $ action fix)
b47ba97b 107
4c2683dd 108withoutFixture :: Actions db a -> FixtureContext db fix -> IO a
b47ba97b 109withoutFixture action (db, _) =
4c2683dd 110 usingConnectionPool (pool db) (transactionally_ action)
b47ba97b 111
aa94c1a5
R
112-- | Helper for writing tests. Wrapper around 'it' that uses the passed
113-- in 'TestDB' to run a db transaction automatically for the test.
4c2683dd 114itDB :: String -> Actions db a -> SpecWith (FixtureContext db ())
b47ba97b
AD
115itDB msg action = it msg $ void . withoutFixture action
116
117-- | Helper for writing tests. Wrapper around 'it' that uses the passed
118-- in 'TestDB' to run a db transaction automatically for the test,
119-- plus the result of the fixtures.
4c2683dd 120itDBF :: String -> (fix -> Actions db a) -> SpecWith (FixtureContext db fix)
b47ba97b
AD
121itDBF msg action = it msg $ void . withFixture action
122
4c2683dd 123itDBF_ :: String -> Actions db a -> SpecWith (FixtureContext db fix)
b47ba97b 124itDBF_ msg action = it msg $ void . withoutFixture action
aa94c1a5
R
125
126-- | Wraps 'describe' with a
127--
128-- @
129-- 'beforeAll' ('setupDB' migrate)
130-- @
131--
132-- hook for creating a db and a
133--
134-- @
135-- 'afterAll' 'teardownDB'
136-- @
137--
138-- hook for stopping a db.
139describeDB
4c2683dd
AD
140 :: Migratory def (IsoQ (Indexed PQ IO ()))
141 => Migrations def db0 db
142 -> Fixtures db ()
aa94c1a5 143 -> String
4c2683dd 144 -> SpecWith (FixtureContext db ())
aa94c1a5
R
145 -> Spec
146describeDB migrate fixture str =
b47ba97b
AD
147 beforeAll (setupDB migrate fixture) . afterAll (teardownDB migrate . fst) . describe str
148
149-- | Like `decribeDB`, but allow fixtures to pass
150-- | a result to all specs
151describeFixtures
4c2683dd
AD
152 :: Migratory def (IsoQ (Indexed PQ IO ()))
153 => Migrations def db0 db
154 -> Fixtures db fix
b47ba97b 155 -> String
4c2683dd 156 -> SpecWith (FixtureContext db fix)
b47ba97b
AD
157 -> Spec
158describeFixtures migrate fixture str =
159 beforeAll (setupDB migrate fixture) . afterAll (teardownDB migrate . fst) . describe str