{-# LANGUAGE GeneralizedNewtypeDeriving, CPP #-}
module TsWeb.Db
( module Database.Beam
, TxOpt(..)
, QueryResult(..)
, ExecResult(..)
, runSelectReturningList
, runSelectReturningOne
, query
, queryMaybe
, queryList
, execute
) where
import qualified TsWeb.Types.Db as Db
import TsWeb.Action (getExtra)
import TsWeb.Types (TsActionCtxT)
import TsWeb.Types.Db (ReadOnlyPool, ReadWritePool)
import qualified Database.Beam as Beam
import Control.Exception (catch, try)
import Data.HVect (ListContains)
import Database.Beam hiding (runSelectReturningList, runSelectReturningOne)
import Database.Beam.Postgres (Pg, Postgres)
import Database.PostgreSQL.Simple (SqlError(..))
import Database.PostgreSQL.Simple.Errors
( ConstraintViolation(..)
, constraintViolationE
)
#if MIN_VERSION_beam_core(0, 8, 0)
type Sel a = SqlSelect Postgres a
#else
import Database.Beam.Postgres (PgSelectSyntax)
type Sel a = SqlSelect PgSelectSyntax a
#endif
class ReadOnlyM m where
runSelectReturningOne ::
FromBackendRow Postgres a => Sel a -> m (Maybe a)
runSelectReturningList ::
FromBackendRow Postgres a => Sel a -> m [a]
instance ReadOnlyM Pg where
runSelectReturningOne = Beam.runSelectReturningOne
runSelectReturningList = Beam.runSelectReturningList
newtype RoPg a = RoPg
{ _fromRoPg :: Pg a
} deriving (Functor, Applicative, Monad)
instance ReadOnlyM RoPg where
runSelectReturningOne = RoPg . Beam.runSelectReturningOne
runSelectReturningList = RoPg . Beam.runSelectReturningList
data TxOpt
= NoTx
| WithTx
deriving (Eq, Ord, Enum, Bounded, Show)
data QueryResult a
= QSimply a
| QError SqlError
deriving (Eq, Show)
query ::
ListContains n ReadOnlyPool xs
=> TxOpt
-> RoPg a
-> TsActionCtxT lts xs sessdata (QueryResult a)
query opt (RoPg act) = do
ropool :: ReadOnlyPool <- getExtra
liftIO $ catch (QSimply <$> Db.withConnection ropool io) (pure . QError)
where
io conn =
case opt of
NoTx -> Db.readOnly conn act
WithTx -> Db.withTransaction conn $ Db.readOnly conn act
queryMaybe ::
(ListContains n ReadOnlyPool xs, FromBackendRow Postgres a)
=> Sel a
-> TsActionCtxT lts xs sessdata (QueryResult (Maybe a))
queryMaybe = query NoTx . runSelectReturningOne
queryList ::
(ListContains n ReadOnlyPool xs, FromBackendRow Postgres a)
=> Sel a
-> TsActionCtxT lts xs sessdata (QueryResult [a])
queryList = query NoTx . runSelectReturningList
data ExecResult a
= ESimply a
| EConstraint SqlError
ConstraintViolation
| EError SqlError
deriving (Eq, Show)
execute ::
ListContains n ReadWritePool xs
=> TxOpt
-> Pg a
-> TsActionCtxT lts xs sessdata (ExecResult a)
execute opt act = do
rwpool <- getExtra
liftIO $ handleError rwpool
where
handleError rwpool =
try (Db.withConnection rwpool io) >>= \case
Right a -> return $ ESimply a
Left err ->
case constraintViolationE err of
Nothing -> return $ EError err
Just (s, c) -> return $ EConstraint s c
io conn =
case opt of
NoTx -> Db.readWrite conn act
WithTx -> Db.withTransaction conn $ Db.readWrite conn act