{-# LANGUAGE CPP #-}
module Database.Persist.Sql.Lifted
(
MonadSqlTx (..)
, HasSqlBackend (..)
, SqlBackend
, MonadSqlBackend (..)
, liftSql
, get
, getBy
, getByValue
, getEntity
, getJust
, getJustEntity
, getMany
, select
, selectOne
, selectFirst
, selectKeysList
, selectList
, selectCount
, selectExists
, count
, exists
, existsBy
, insertSelect
, insertSelectCount
, insert
, insert_
, insertBy
, insertEntity
, insertEntityMany
, insertKey
, insertMany
, insertMany_
, insertRecord
, insertUnique
, insertUnique_
, insertUniqueEntity
, update
, updateCount
, update'
, updateGet
, updateGetEntity
, updateWhere
, updateWhereCount
, replace
, replaceUnique
, repsert
, repsertMany
, upsert
, upsertBy
, putMany
, checkUnique
, checkUniqueUpdateable
, onlyUnique
, delete
, deleteKey
, deleteBy
, deleteWhere
, deleteCount
, deleteWhereCount
, transactionSave
, transactionSaveWithIsolation
, transactionUndo
, transactionUndoWithIsolation
, rawSql
, rawExecute
, rawExecuteCount
, getFieldName
, getTableName
, renderQueryDelete
, renderQueryInsertInto
, renderQuerySelect
, renderQueryToText
, renderQueryUpdate
) where
#if MIN_VERSION_base(4,17,0)
import Data.Type.Equality (type (~))
#endif
import Prelude (Integral)
import Control.Applicative (pure)
import Data.Bool (Bool (..))
import Data.Function (($))
import Data.Functor (($>), (<$>))
import Data.Maybe (maybe)
import Database.Esqueleto.Experimental (PersistField, Value (..), countRows)
import Database.Persist (Key, PersistEntity (PersistEntityBackend), Update)
import Database.Persist.Sql.Lifted.Core
import Database.Persist.Sql.Lifted.Esqueleto
import Database.Persist.Sql.Lifted.Expression qualified as SqlExpr
import Database.Persist.Sql.Lifted.Persistent hiding (delete, update)
import Database.Persist.Sql.Lifted.Persistent qualified as Persistent
import Database.Persist.Sql.Lifted.Query (SqlQuery)
import Database.Persist.Types (Entity (..))
import GHC.Stack (HasCallStack)
update'
:: forall a m
. ( HasCallStack
, MonadSqlBackend m
, PersistEntity a
, PersistEntityBackend a ~ SqlBackend
)
=> Key a
-> [Update a]
-> m ()
update' :: forall a (m :: * -> *).
(HasCallStack, MonadSqlBackend m, PersistEntity a,
PersistEntityBackend a ~ SqlBackend) =>
Key a -> [Update a] -> m ()
update' = Key a -> [Update a] -> m ()
forall a (m :: * -> *).
(HasCallStack, MonadSqlBackend m, PersistEntity a,
PersistEntityBackend a ~ SqlBackend) =>
Key a -> [Update a] -> m ()
Persistent.update
updateGetEntity
:: forall a m
. ( HasCallStack
, MonadSqlBackend m
, PersistEntity a
, PersistEntityBackend a ~ SqlBackend
)
=> Key a
-> [Update a]
-> m (Entity a)
updateGetEntity :: forall a (m :: * -> *).
(HasCallStack, MonadSqlBackend m, PersistEntity a,
PersistEntityBackend a ~ SqlBackend) =>
Key a -> [Update a] -> m (Entity a)
updateGetEntity Key a
k [Update a]
us = Key a -> a -> Entity a
forall record. Key record -> record -> Entity record
Entity Key a
k (a -> Entity a) -> m a -> m (Entity a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key a -> [Update a] -> m a
forall a (m :: * -> *).
(HasCallStack, MonadSqlBackend m, PersistEntity a,
PersistEntityBackend a ~ SqlBackend) =>
Key a -> [Update a] -> m a
updateGet Key a
k [Update a]
us
selectCount
:: forall a m
. (HasCallStack, Integral a, MonadSqlBackend m, PersistField a)
=> SqlQuery ()
-> m a
selectCount :: forall a (m :: * -> *).
(HasCallStack, Integral a, MonadSqlBackend m, PersistField a) =>
SqlQuery () -> m a
selectCount SqlQuery ()
q =
a -> (Value a -> a) -> Maybe (Value a) -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
0 Value a -> a
forall a. Value a -> a
unValue (Maybe (Value a) -> a) -> m (Maybe (Value a)) -> m a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SqlQuery (SqlExpr (Value a)) -> m (Maybe (Value a))
forall a r (m :: * -> *).
(HasCallStack, MonadSqlBackend m, SqlSelect a r) =>
SqlQuery a -> m (Maybe r)
selectOne (SqlQuery ()
q SqlQuery () -> SqlExpr (Value a) -> SqlQuery (SqlExpr (Value a))
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> SqlExpr (Value a)
forall a. Num a => SqlExpr (Value a)
countRows)
selectExists
:: forall m. (HasCallStack, MonadSqlBackend m) => SqlQuery () -> m Bool
selectExists :: forall (m :: * -> *).
(HasCallStack, MonadSqlBackend m) =>
SqlQuery () -> m Bool
selectExists SqlQuery ()
q = Bool -> (Value Bool -> Bool) -> Maybe (Value Bool) -> Bool
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Bool
False Value Bool -> Bool
forall a. Value a -> a
unValue (Maybe (Value Bool) -> Bool) -> m (Maybe (Value Bool)) -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SqlQuery (SqlExpr (Value Bool)) -> m (Maybe (Value Bool))
forall a r (m :: * -> *).
(HasCallStack, MonadSqlBackend m, SqlSelect a r) =>
SqlQuery a -> m (Maybe r)
selectOne (SqlExpr (Value Bool) -> SqlQuery (SqlExpr (Value Bool))
forall a. a -> SqlQuery a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Value Bool) -> SqlQuery (SqlExpr (Value Bool)))
-> SqlExpr (Value Bool) -> SqlQuery (SqlExpr (Value Bool))
forall a b. (a -> b) -> a -> b
$ SqlQuery () -> SqlExpr (Value Bool)
SqlExpr.exists SqlQuery ()
q)