{-# LANGUAGE AllowAmbiguousTypes #-}
module Database.GP.GenericPersistence
  ( selectById,
    select,
    count,
    entitiesFromRows,
    sql,
    persist,
    upsert,
    insert,
    insertMany,
    update,
    updateMany,
    delete,
    deleteById,
    deleteMany,
    deleteManyById,
    setupTable,
    defaultSqliteMapping,
    defaultPostgresMapping,
    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,
                                                     setupTable, sql)
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 <- Conn -> id -> IO (Either PersistenceException a)
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
_) -> Maybe a -> IO (Maybe a)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe a
forall a. Maybe a
Nothing
    Left PersistenceException
ex                        -> PersistenceException -> IO (Maybe a)
forall a e. Exception e => e -> a
throw PersistenceException
ex
    Right a
entity                   -> Maybe a -> IO (Maybe a)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe a -> IO (Maybe a)) -> Maybe a -> IO (Maybe a)
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
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        -> PersistenceException -> IO [a]
forall a e. Exception e => e -> a
throw PersistenceException
ex
    Right [a]
entities -> [a] -> IO [a]
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [a]
entities
count :: forall a. (Entity a) => Conn -> WhereClauseExpr -> IO Int
count :: forall a. Entity a => Conn -> WhereClauseExpr -> IO Int
count Conn
conn WhereClauseExpr
whereClause = do
  Either PersistenceException Int
eitherExCount <- forall a.
Entity a =>
Conn -> WhereClauseExpr -> IO (Either PersistenceException Int)
GpSafe.count @a Conn
conn WhereClauseExpr
whereClause
  case Either PersistenceException Int
eitherExCount of
    Left PersistenceException
ex   -> PersistenceException -> IO Int
forall a e. Exception e => e -> a
throw PersistenceException
ex
    Right Int
cnt -> Int -> IO Int
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Int
cnt
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 -> PersistenceException -> IO a
forall a e. Exception e => e -> a
throw PersistenceException
ex
    Right a
a -> a -> IO a
forall a. a -> IO 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 = (IO (Either PersistenceException [a]) -> IO [a]
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) (([[SqlValue]] -> IO (Either PersistenceException [a]))
 -> [[SqlValue]] -> IO [a])
-> (Conn -> [[SqlValue]] -> IO (Either PersistenceException [a]))
-> Conn
-> [[SqlValue]]
-> IO [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Conn -> [[SqlValue]] -> IO (Either PersistenceException [a])
forall a.
Entity a =>
Conn -> [[SqlValue]] -> IO (Either PersistenceException [a])
GpSafe.entitiesFromRows
{-# DEPRECATED persist "use upsert instead" #-}
persist :: forall a. (Entity a) => Conn -> a -> IO ()
persist :: forall a. Entity a => Conn -> a -> IO ()
persist = Conn -> a -> IO ()
forall a. Entity a => Conn -> a -> IO ()
upsert
upsert :: forall a. (Entity a) => Conn -> a -> IO ()
upsert :: forall a. Entity a => Conn -> a -> IO ()
upsert = (IO (Either PersistenceException ()) -> IO ()
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) ((a -> IO (Either PersistenceException ())) -> a -> IO ())
-> (Conn -> a -> IO (Either PersistenceException ()))
-> Conn
-> a
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Conn -> a -> IO (Either PersistenceException ())
forall a.
Entity a =>
Conn -> a -> IO (Either PersistenceException ())
GpSafe.upsert
insert :: forall a. (Entity a) => Conn -> a -> IO a
insert :: forall a. Entity a => Conn -> a -> IO a
insert = (IO (Either PersistenceException a) -> IO a
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) ((a -> IO (Either PersistenceException a)) -> a -> IO a)
-> (Conn -> a -> IO (Either PersistenceException a))
-> Conn
-> a
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Conn -> a -> IO (Either PersistenceException a)
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 = (IO (Either PersistenceException ()) -> IO ()
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) (([a] -> IO (Either PersistenceException ())) -> [a] -> IO ())
-> (Conn -> [a] -> IO (Either PersistenceException ()))
-> Conn
-> [a]
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Conn -> [a] -> IO (Either PersistenceException ())
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 ()
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) ((a -> IO (Either PersistenceException ())) -> a -> IO ())
-> (Conn -> a -> IO (Either PersistenceException ()))
-> Conn
-> a
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Conn -> a -> IO (Either PersistenceException ())
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 ()
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) (([a] -> IO (Either PersistenceException ())) -> [a] -> IO ())
-> (Conn -> [a] -> IO (Either PersistenceException ()))
-> Conn
-> [a]
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Conn -> [a] -> IO (Either PersistenceException ())
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 ()
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) ((a -> IO (Either PersistenceException ())) -> a -> IO ())
-> (Conn -> a -> IO (Either PersistenceException ()))
-> Conn
-> a
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Conn -> a -> IO (Either PersistenceException ())
forall a.
Entity a =>
Conn -> a -> IO (Either PersistenceException ())
GpSafe.delete
deleteById :: forall a id. (Entity a, Convertible id SqlValue) => Conn -> id -> IO ()
deleteById :: forall a id.
(Entity a, Convertible id SqlValue) =>
Conn -> id -> IO ()
deleteById = (IO (Either PersistenceException ()) -> IO ()
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) ((id -> IO (Either PersistenceException ())) -> id -> IO ())
-> (Conn -> id -> IO (Either PersistenceException ()))
-> Conn
-> id
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a id.
(Entity a, Convertible id SqlValue) =>
Conn -> id -> IO (Either PersistenceException ())
GpSafe.deleteById @a
deleteMany :: forall a. (Entity a) => Conn -> [a] -> IO ()
deleteMany :: forall a. Entity a => Conn -> [a] -> IO ()
deleteMany = (IO (Either PersistenceException ()) -> IO ()
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) (([a] -> IO (Either PersistenceException ())) -> [a] -> IO ())
-> (Conn -> [a] -> IO (Either PersistenceException ()))
-> Conn
-> [a]
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Conn -> [a] -> IO (Either PersistenceException ())
forall a.
Entity a =>
Conn -> [a] -> IO (Either PersistenceException ())
GpSafe.deleteMany
deleteManyById :: forall a id. (Entity a, Convertible id SqlValue) => Conn -> [id] -> IO ()
deleteManyById :: forall a id.
(Entity a, Convertible id SqlValue) =>
Conn -> [id] -> IO ()
deleteManyById = (IO (Either PersistenceException ()) -> IO ()
forall a. IO (Either PersistenceException a) -> IO a
fromEitherExOrA .) (([id] -> IO (Either PersistenceException ())) -> [id] -> IO ())
-> (Conn -> [id] -> IO (Either PersistenceException ()))
-> Conn
-> [id]
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a id.
(Entity a, Convertible id SqlValue) =>
Conn -> [id] -> IO (Either PersistenceException ())
GpSafe.deleteManyById @a