{-# LANGUAGE AllowAmbiguousTypes #-}
module Database.GP.GenericPersistence
( selectById,
select,
entitiesFromRows,
sql,
persist,
insert,
insertMany,
update,
updateMany,
delete,
deleteMany,
setupTableFor,
Conn(..),
connect,
Database(..),
TxHandling (..),
ConnectionPool,
createConnPool,
withResource,
Entity (..),
GToRow,
GFromRow,
columnNameFor,
maybeFieldTypeFor,
TypeInfo (..),
typeInfo,
PersistenceException(..),
WhereClauseExpr,
Field,
field,
(&&.),
(||.),
(=.),
(>.),
(<.),
(>=.),
(<=.),
(<>.),
like,
between,
in',
isNull,
not',
sqlFun,
allEntries,
byId,
orderBy,
SortOrder (..),
limit,
limitOffset,
NonEmpty(..)
)
where
import Control.Exception
import Data.Convertible (Convertible)
import Database.GP.Conn
import Database.GP.Entity
import Database.GP.GenericPersistenceSafe (PersistenceException, sql, setupTableFor)
import qualified Database.GP.GenericPersistenceSafe as GpSafe
import Database.GP.SqlGenerator
import Database.GP.TypeInfo
import Database.HDBC
selectById :: forall a id. (Entity a, Convertible id SqlValue) => Conn -> id -> IO (Maybe a)
selectById :: forall a id.
(Entity a, Convertible id SqlValue) =>
Conn -> id -> IO (Maybe a)
selectById Conn
conn id
idx = do
Either PersistenceException a
eitherExEntity <- forall a id.
(Entity a, Convertible id SqlValue) =>
Conn -> id -> IO (Either PersistenceException a)
GpSafe.selectById Conn
conn id
idx
case Either PersistenceException a
eitherExEntity of
Left (GpSafe.EntityNotFound String
_) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
Left PersistenceException
ex -> forall a e. Exception e => e -> a
throw PersistenceException
ex
Right a
entity -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just a
entity
select :: forall a. (Entity a) => Conn -> WhereClauseExpr -> IO [a]
select :: forall a. Entity a => Conn -> WhereClauseExpr -> IO [a]
select Conn
conn WhereClauseExpr
whereClause = do
Either PersistenceException [a]
eitherExEntities <- forall a.
Entity a =>
Conn -> WhereClauseExpr -> IO (Either PersistenceException [a])
GpSafe.select @a Conn
conn WhereClauseExpr
whereClause
case Either PersistenceException [a]
eitherExEntities of
Left PersistenceException
ex -> forall a e. Exception e => e -> a
throw PersistenceException
ex
Right [a]
entities -> forall (f :: * -> *) a. Applicative f => a -> f a
pure [a]
entities
fromEitherExOrA :: IO (Either PersistenceException a) -> IO a
fromEitherExOrA :: forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA IO (Either PersistenceException a)
ioEitherExUnit = do
Either PersistenceException a
eitherExUnit <- IO (Either PersistenceException a)
ioEitherExUnit
case Either PersistenceException a
eitherExUnit of
Left PersistenceException
ex -> forall a e. Exception e => e -> a
throw PersistenceException
ex
Right a
a -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a
entitiesFromRows :: forall a. (Entity a) => Conn -> [[SqlValue]] -> IO [a]
entitiesFromRows :: forall a. Entity a => Conn -> [[SqlValue]] -> IO [a]
entitiesFromRows = (forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> [[SqlValue]] -> IO (Either PersistenceException [a])
GpSafe.entitiesFromRows
persist :: forall a. (Entity a) => Conn -> a -> IO ()
persist :: forall a. Entity a => Conn -> a -> IO ()
persist = (forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> a -> IO (Either PersistenceException ())
GpSafe.persist
insert :: forall a. (Entity a) => Conn -> a -> IO a
insert :: forall a. Entity a => Conn -> a -> IO a
insert = (forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> a -> IO (Either PersistenceException a)
GpSafe.insert
insertMany :: forall a. (Entity a) => Conn -> [a] -> IO ()
insertMany :: forall a. Entity a => Conn -> [a] -> IO ()
insertMany = (forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> [a] -> IO (Either PersistenceException ())
GpSafe.insertMany
update :: forall a. (Entity a) => Conn -> a -> IO ()
update :: forall a. Entity a => Conn -> a -> IO ()
update = (forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> a -> IO (Either PersistenceException ())
GpSafe.update
updateMany :: forall a. (Entity a) => Conn -> [a] -> IO ()
updateMany :: forall a. Entity a => Conn -> [a] -> IO ()
updateMany = (forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> [a] -> IO (Either PersistenceException ())
GpSafe.updateMany
delete :: forall a. (Entity a) => Conn -> a -> IO ()
delete :: forall a. Entity a => Conn -> a -> IO ()
delete = (forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> a -> IO (Either PersistenceException ())
GpSafe.delete
deleteMany :: forall a. (Entity a) => Conn -> [a] -> IO ()
deleteMany :: forall a. Entity a => Conn -> [a] -> IO ()
deleteMany = (forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> [a] -> IO (Either PersistenceException ())
GpSafe.deleteMany