{-# LANGUAGE AllowAmbiguousTypes #-}
module Database.GP.GenericPersistence
( selectById,
select,
entitiesFromRows,
persist,
insert,
insertMany,
update,
updateMany,
delete,
deleteMany,
setupTableFor,
idValue,
Conn(..),
connect,
Database(..),
ConnectionPool,
createConnPool,
withResource,
Entity (..),
GToRow,
GFromRow,
columnNameFor,
maybeFieldTypeFor,
toString,
TypeInfo (..),
typeInfo,
PersistenceException(..),
WhereClauseExpr,
Field,
field,
(&&.),
(||.),
(=.),
(>.),
(<.),
(>=.),
(<=.),
(<>.),
like,
contains,
between,
in',
isNull,
not',
sqlFun,
allEntries,
byId,
)
where
import Control.Exception
import Control.Monad (when)
import Data.Convertible (Convertible)
import Data.List (elemIndex)
import Database.GP.Conn
import Database.GP.Entity
import Database.GP.GenericPersistenceSafe (PersistenceException)
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
entitiesFromRows :: forall a. (Entity a) => Conn -> [[SqlValue]] -> IO [a]
entitiesFromRows :: forall a. Entity a => Conn -> [[SqlValue]] -> IO [a]
entitiesFromRows Conn
conn [[SqlValue]]
rows = do
Either PersistenceException [a]
eitherExEntities <- forall a.
Entity a =>
Conn -> [[SqlValue]] -> IO (Either PersistenceException [a])
GpSafe.entitiesFromRows @a Conn
conn [[SqlValue]]
rows
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
fromEitherExUnit :: IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit :: IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit IO (Either PersistenceException ())
ioEitherExUnit = do
Either PersistenceException ()
eitherExUnit <- IO (Either PersistenceException ())
ioEitherExUnit
case Either PersistenceException ()
eitherExUnit of
Left PersistenceException
ex -> forall a e. Exception e => e -> a
throw PersistenceException
ex
Right ()
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
persist :: forall a. (Entity a) => Conn -> a -> IO ()
persist :: forall a. Entity a => Conn -> a -> IO ()
persist = (IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit .) 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 ()
insert :: forall a. Entity a => Conn -> a -> IO ()
insert = (IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> a -> IO (Either PersistenceException ())
GpSafe.insert
insertMany :: forall a. (Entity a) => Conn -> [a] -> IO ()
insertMany :: forall a. Entity a => Conn -> [a] -> IO ()
insertMany = (IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit .) 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 = (IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit .) 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 = (IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit .) 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 = (IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit .) 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 = (IO (Either PersistenceException ()) -> IO ()
fromEitherExUnit .) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
Entity a =>
Conn -> [a] -> IO (Either PersistenceException ())
GpSafe.deleteMany
setupTableFor :: forall a. (Entity a) => Conn -> IO ()
setupTableFor :: forall a. Entity a => Conn -> IO ()
setupTableFor Conn
conn = do
forall conn. IConnection conn => conn -> String -> IO ()
runRaw Conn
conn forall a b. (a -> b) -> a -> b
$ forall a. Entity a => String
dropTableStmtFor @a
forall conn. IConnection conn => conn -> String -> IO ()
runRaw Conn
conn forall a b. (a -> b) -> a -> b
$ forall a. Entity a => Database -> String
createTableStmtFor @a (Conn -> Database
db Conn
conn)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Conn -> Bool
implicitCommit Conn
conn) forall a b. (a -> b) -> a -> b
$ forall conn. IConnection conn => conn -> IO ()
commit Conn
conn
idValue :: forall a. (Entity a) => Conn -> a -> IO SqlValue
idValue :: forall a. Entity a => Conn -> a -> IO SqlValue
idValue Conn
conn a
x = do
[SqlValue]
sqlValues <- forall a. Entity a => Conn -> a -> IO [SqlValue]
toRow Conn
conn a
x
forall (m :: * -> *) a. Monad m => a -> m a
return ([SqlValue]
sqlValues forall a. [a] -> Int -> a
!! Int
idFieldIndex)
where
idFieldIndex :: Int
idFieldIndex = forall a. Entity a => String -> Int
fieldIndex @a (forall a. Entity a => String
idField @a)
fieldIndex :: forall a. (Entity a) => String -> Int
fieldIndex :: forall a. Entity a => String -> Int
fieldIndex String
fieldName =
forall a. String -> Maybe a -> a
expectJust
(String
"Field " forall a. [a] -> [a] -> [a]
++ String
fieldName forall a. [a] -> [a] -> [a]
++ String
" is not present in type " forall a. [a] -> [a] -> [a]
++ forall {k} (a :: k). TypeInfo a -> String
constructorName TypeInfo a
ti)
(forall a. Eq a => a -> [a] -> Maybe Int
elemIndex String
fieldName [String]
fieldList)
where
ti :: TypeInfo a
ti = forall a.
(HasConstructor (Rep a), HasSelectors (Rep a), Generic a) =>
TypeInfo a
typeInfo @a
fieldList :: [String]
fieldList = forall {k} (a :: k). TypeInfo a -> [String]
fieldNames TypeInfo a
ti
expectJust :: String -> Maybe a -> a
expectJust :: forall a. String -> Maybe a -> a
expectJust String
_ (Just a
x) = a
x
expectJust String
err Maybe a
Nothing = forall a. HasCallStack => String -> a
error (String
"expectJust " forall a. [a] -> [a] -> [a]
++ String
err)