{-# LANGUAGE CPP #-}
module TsWeb.Types.Db
( SomeConn
, ReadOnlyConn
, ReadWriteConn
, ReadOnlyPool
, ReadWritePool
, ReadOnly
, ReadWrite
, HostName
, DbName
, SubPools
, KeepOpen
, count
, pool
, withConnection
, connect
, withSavepoint
, withTransaction
, readOnly
, readOnlyDebug
, readWrite
, readWriteDebug
) where
import qualified Database.Beam.Postgres as PG
import qualified Database.PostgreSQL.Simple as Simple
import Data.Pool (Pool, createPool, withResource)
import Data.Tagged (Tagged(..))
import Data.Time.Clock (NominalDiffTime)
import Database.Beam hiding (runSelectReturningList, runSelectReturningOne)
import Database.Beam.Postgres
( Connection
, Pg
, runBeamPostgres
, runBeamPostgresDebug
)
import qualified Database.Beam.Query.Internal as BI
#if MIN_VERSION_beam_core(0, 8, 0)
import Database.Beam.Postgres (Postgres)
#else
import Database.Beam.Postgres.Syntax (PgExpressionSyntax, PgSelectSyntax)
#endif
#if MIN_VERSION_beam_core(0, 8, 0)
count ::
(BI.ProjectibleWithPredicate BI.AnyType Postgres (BI.WithExprContext
(BI.BeamSqlBackendExpressionSyntax' Postgres)) t)
=> Q Postgres db (BI.QNested s0) t
-> Q Postgres db s0 (QGenExpr QValueContext Postgres s0 Int)
#else
count ::
BI.ProjectibleWithPredicate BI.AnyType PgExpressionSyntax t
=> Q PgSelectSyntax db (BI.QNested s0) t
-> Q PgSelectSyntax db s0 (QGenExpr QValueContext PgExpressionSyntax s0 Int)
#endif
count = aggregate_ (const countAll_)
data ReadOnly
data ReadWrite
type SomeConn t = Tagged t Connection
type ReadOnlyConn = SomeConn ReadOnly
type ReadWriteConn = SomeConn ReadWrite
type ReadOnlyPool = Pool ReadOnlyConn
type ReadWritePool = Pool ReadWriteConn
type HostName = String
type DbName = String
type SubPools = Int
type KeepOpen = Int
pool ::
HostName
-> DbName
-> String
-> SubPools
-> NominalDiffTime
-> KeepOpen
-> IO (Pool (SomeConn t))
pool host db username =
createPool (connect host db username) (PG.close . unTagged)
withConnection :: Pool (SomeConn a) -> (SomeConn a -> IO b) -> IO b
withConnection = withResource
connect :: HostName -> DbName -> String -> IO (SomeConn t)
connect host db username =
print db >>
Tagged <$>
(PG.connect $
PG.defaultConnectInfo
{PG.connectUser = username, PG.connectDatabase = db, PG.connectHost = host})
withSavepoint :: SomeConn t -> IO a -> IO a
withSavepoint (Tagged c) = Simple.withSavepoint c
withTransaction :: SomeConn t -> IO a -> IO a
withTransaction (Tagged c) = Simple.withTransaction c
readOnly :: SomeConn t -> Pg a -> IO a
readOnly (Tagged conn) = runBeamPostgres conn
readOnlyDebug :: SomeConn t -> Pg a -> IO a
readOnlyDebug (Tagged conn) = runBeamPostgresDebug putStrLn conn
readWrite :: ReadWriteConn -> Pg a -> IO a
readWrite (Tagged conn) = runBeamPostgres conn
readWriteDebug :: ReadWriteConn -> Pg a -> IO a
readWriteDebug (Tagged conn) = runBeamPostgresDebug putStrLn conn