{-# LANGUAGE ExplicitForAll #-}
module Database.Persist.Class.PersistQuery
( PersistQueryRead (..)
, PersistQueryWrite (..)
, selectSource
, selectKeys
, selectList
, selectKeysList
) where
import Control.Monad.IO.Class (MonadIO, liftIO)
import Control.Monad.Reader (ReaderT, MonadReader)
import Control.Monad.Trans.Resource (MonadResource, release)
import Data.Acquire (Acquire, allocateAcquire, with)
import Data.Conduit (ConduitM, (.|), await, runConduit)
import qualified Data.Conduit.List as CL
import Database.Persist.Class.PersistStore
import Database.Persist.Class.PersistEntity
class (PersistCore backend, PersistStoreRead backend) => PersistQueryRead backend where
selectSourceRes
:: (PersistRecordBackend record backend, MonadIO m1, MonadIO m2)
=> [Filter record]
-> [SelectOpt record]
-> ReaderT backend m1 (Acquire (ConduitM () (Entity record) m2 ()))
selectFirst :: (MonadIO m, PersistRecordBackend record backend)
=> [Filter record]
-> [SelectOpt record]
-> ReaderT backend m (Maybe (Entity record))
selectFirst [Filter record]
filts [SelectOpt record]
opts = do
Acquire (ConduitM () (Entity record) IO ())
srcRes <- [Filter record]
-> [SelectOpt record]
-> ReaderT backend m (Acquire (ConduitM () (Entity record) IO ()))
forall backend record (m1 :: * -> *) (m2 :: * -> *).
(PersistQueryRead backend, PersistRecordBackend record backend,
MonadIO m1, MonadIO m2) =>
[Filter record]
-> [SelectOpt record]
-> ReaderT backend m1 (Acquire (ConduitM () (Entity record) m2 ()))
selectSourceRes [Filter record]
filts (Int -> SelectOpt record
forall record. Int -> SelectOpt record
LimitTo Int
1 SelectOpt record -> [SelectOpt record] -> [SelectOpt record]
forall a. a -> [a] -> [a]
: [SelectOpt record]
opts)
IO (Maybe (Entity record))
-> ReaderT backend m (Maybe (Entity record))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Maybe (Entity record))
-> ReaderT backend m (Maybe (Entity record)))
-> IO (Maybe (Entity record))
-> ReaderT backend m (Maybe (Entity record))
forall a b. (a -> b) -> a -> b
$ Acquire (ConduitM () (Entity record) IO ())
-> (ConduitM () (Entity record) IO ()
-> IO (Maybe (Entity record)))
-> IO (Maybe (Entity record))
forall (m :: * -> *) a b.
MonadUnliftIO m =>
Acquire a -> (a -> m b) -> m b
with Acquire (ConduitM () (Entity record) IO ())
srcRes (\ConduitM () (Entity record) IO ()
src -> ConduitT () Void IO (Maybe (Entity record))
-> IO (Maybe (Entity record))
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void IO (Maybe (Entity record))
-> IO (Maybe (Entity record)))
-> ConduitT () Void IO (Maybe (Entity record))
-> IO (Maybe (Entity record))
forall a b. (a -> b) -> a -> b
$ ConduitM () (Entity record) IO ()
src ConduitM () (Entity record) IO ()
-> ConduitM (Entity record) Void IO (Maybe (Entity record))
-> ConduitT () Void IO (Maybe (Entity record))
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM (Entity record) Void IO (Maybe (Entity record))
forall (m :: * -> *) i. Monad m => Consumer i m (Maybe i)
await)
selectKeysRes
:: (MonadIO m1, MonadIO m2, PersistRecordBackend record backend)
=> [Filter record]
-> [SelectOpt record]
-> ReaderT backend m1 (Acquire (ConduitM () (Key record) m2 ()))
count :: (MonadIO m, PersistRecordBackend record backend)
=> [Filter record] -> ReaderT backend m Int
exists :: (MonadIO m, PersistRecordBackend record backend)
=> [Filter record] -> ReaderT backend m Bool
class (PersistQueryRead backend, PersistStoreWrite backend) => PersistQueryWrite backend where
updateWhere :: (MonadIO m, PersistRecordBackend record backend)
=> [Filter record] -> [Update record] -> ReaderT backend m ()
deleteWhere :: (MonadIO m, PersistRecordBackend record backend)
=> [Filter record] -> ReaderT backend m ()
selectSource
:: forall record backend m. (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m)
=> [Filter record]
-> [SelectOpt record]
-> ConduitM () (Entity record) m ()
selectSource :: [Filter record]
-> [SelectOpt record] -> ConduitM () (Entity record) m ()
selectSource [Filter record]
filts [SelectOpt record]
opts = do
Acquire (ConduitM () (Entity record) m ())
srcRes <- ReaderT backend IO (Acquire (ConduitM () (Entity record) m ()))
-> ConduitT
() (Entity record) m (Acquire (ConduitM () (Entity record) m ()))
forall (m :: * -> *) backend b.
(MonadIO m, MonadReader backend m) =>
ReaderT backend IO b -> m b
liftPersist (ReaderT backend IO (Acquire (ConduitM () (Entity record) m ()))
-> ConduitT
() (Entity record) m (Acquire (ConduitM () (Entity record) m ())))
-> ReaderT backend IO (Acquire (ConduitM () (Entity record) m ()))
-> ConduitT
() (Entity record) m (Acquire (ConduitM () (Entity record) m ()))
forall a b. (a -> b) -> a -> b
$ [Filter record]
-> [SelectOpt record]
-> ReaderT backend IO (Acquire (ConduitM () (Entity record) m ()))
forall backend record (m1 :: * -> *) (m2 :: * -> *).
(PersistQueryRead backend, PersistRecordBackend record backend,
MonadIO m1, MonadIO m2) =>
[Filter record]
-> [SelectOpt record]
-> ReaderT backend m1 (Acquire (ConduitM () (Entity record) m2 ()))
selectSourceRes [Filter record]
filts [SelectOpt record]
opts
(ReleaseKey
releaseKey, ConduitM () (Entity record) m ()
src) <- Acquire (ConduitM () (Entity record) m ())
-> ConduitT
() (Entity record) m (ReleaseKey, ConduitM () (Entity record) m ())
forall (m :: * -> *) a.
MonadResource m =>
Acquire a -> m (ReleaseKey, a)
allocateAcquire Acquire (ConduitM () (Entity record) m ())
srcRes
ConduitM () (Entity record) m ()
src
ReleaseKey -> ConduitM () (Entity record) m ()
forall (m :: * -> *). MonadIO m => ReleaseKey -> m ()
release ReleaseKey
releaseKey
selectKeys :: forall record backend m. (PersistQueryRead backend, MonadResource m, PersistRecordBackend record backend, MonadReader backend m)
=> [Filter record]
-> [SelectOpt record]
-> ConduitM () (Key record) m ()
selectKeys :: [Filter record]
-> [SelectOpt record] -> ConduitM () (Key record) m ()
selectKeys [Filter record]
filts [SelectOpt record]
opts = do
Acquire (ConduitM () (Key record) m ())
srcRes <- ReaderT backend IO (Acquire (ConduitM () (Key record) m ()))
-> ConduitT
() (Key record) m (Acquire (ConduitM () (Key record) m ()))
forall (m :: * -> *) backend b.
(MonadIO m, MonadReader backend m) =>
ReaderT backend IO b -> m b
liftPersist (ReaderT backend IO (Acquire (ConduitM () (Key record) m ()))
-> ConduitT
() (Key record) m (Acquire (ConduitM () (Key record) m ())))
-> ReaderT backend IO (Acquire (ConduitM () (Key record) m ()))
-> ConduitT
() (Key record) m (Acquire (ConduitM () (Key record) m ()))
forall a b. (a -> b) -> a -> b
$ [Filter record]
-> [SelectOpt record]
-> ReaderT backend IO (Acquire (ConduitM () (Key record) m ()))
forall backend (m1 :: * -> *) (m2 :: * -> *) record.
(PersistQueryRead backend, MonadIO m1, MonadIO m2,
PersistRecordBackend record backend) =>
[Filter record]
-> [SelectOpt record]
-> ReaderT backend m1 (Acquire (ConduitM () (Key record) m2 ()))
selectKeysRes [Filter record]
filts [SelectOpt record]
opts
(ReleaseKey
releaseKey, ConduitM () (Key record) m ()
src) <- Acquire (ConduitM () (Key record) m ())
-> ConduitT
() (Key record) m (ReleaseKey, ConduitM () (Key record) m ())
forall (m :: * -> *) a.
MonadResource m =>
Acquire a -> m (ReleaseKey, a)
allocateAcquire Acquire (ConduitM () (Key record) m ())
srcRes
ConduitM () (Key record) m ()
src
ReleaseKey -> ConduitM () (Key record) m ()
forall (m :: * -> *). MonadIO m => ReleaseKey -> m ()
release ReleaseKey
releaseKey
selectList :: forall record backend m. (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend)
=> [Filter record]
-> [SelectOpt record]
-> ReaderT backend m [Entity record]
selectList :: [Filter record]
-> [SelectOpt record] -> ReaderT backend m [Entity record]
selectList [Filter record]
filts [SelectOpt record]
opts = do
Acquire (ConduitM () (Entity record) IO ())
srcRes <- [Filter record]
-> [SelectOpt record]
-> ReaderT backend m (Acquire (ConduitM () (Entity record) IO ()))
forall backend record (m1 :: * -> *) (m2 :: * -> *).
(PersistQueryRead backend, PersistRecordBackend record backend,
MonadIO m1, MonadIO m2) =>
[Filter record]
-> [SelectOpt record]
-> ReaderT backend m1 (Acquire (ConduitM () (Entity record) m2 ()))
selectSourceRes [Filter record]
filts [SelectOpt record]
opts
IO [Entity record] -> ReaderT backend m [Entity record]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Entity record] -> ReaderT backend m [Entity record])
-> IO [Entity record] -> ReaderT backend m [Entity record]
forall a b. (a -> b) -> a -> b
$ Acquire (ConduitM () (Entity record) IO ())
-> (ConduitM () (Entity record) IO () -> IO [Entity record])
-> IO [Entity record]
forall (m :: * -> *) a b.
MonadUnliftIO m =>
Acquire a -> (a -> m b) -> m b
with Acquire (ConduitM () (Entity record) IO ())
srcRes (\ConduitM () (Entity record) IO ()
src -> ConduitT () Void IO [Entity record] -> IO [Entity record]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void IO [Entity record] -> IO [Entity record])
-> ConduitT () Void IO [Entity record] -> IO [Entity record]
forall a b. (a -> b) -> a -> b
$ ConduitM () (Entity record) IO ()
src ConduitM () (Entity record) IO ()
-> ConduitM (Entity record) Void IO [Entity record]
-> ConduitT () Void IO [Entity record]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM (Entity record) Void IO [Entity record]
forall (m :: * -> *) a o. Monad m => ConduitT a o m [a]
CL.consume)
selectKeysList :: forall record backend m. (MonadIO m, PersistQueryRead backend, PersistRecordBackend record backend)
=> [Filter record]
-> [SelectOpt record]
-> ReaderT backend m [Key record]
selectKeysList :: [Filter record]
-> [SelectOpt record] -> ReaderT backend m [Key record]
selectKeysList [Filter record]
filts [SelectOpt record]
opts = do
Acquire (ConduitM () (Key record) IO ())
srcRes <- [Filter record]
-> [SelectOpt record]
-> ReaderT backend m (Acquire (ConduitM () (Key record) IO ()))
forall backend (m1 :: * -> *) (m2 :: * -> *) record.
(PersistQueryRead backend, MonadIO m1, MonadIO m2,
PersistRecordBackend record backend) =>
[Filter record]
-> [SelectOpt record]
-> ReaderT backend m1 (Acquire (ConduitM () (Key record) m2 ()))
selectKeysRes [Filter record]
filts [SelectOpt record]
opts
IO [Key record] -> ReaderT backend m [Key record]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [Key record] -> ReaderT backend m [Key record])
-> IO [Key record] -> ReaderT backend m [Key record]
forall a b. (a -> b) -> a -> b
$ Acquire (ConduitM () (Key record) IO ())
-> (ConduitM () (Key record) IO () -> IO [Key record])
-> IO [Key record]
forall (m :: * -> *) a b.
MonadUnliftIO m =>
Acquire a -> (a -> m b) -> m b
with Acquire (ConduitM () (Key record) IO ())
srcRes (\ConduitM () (Key record) IO ()
src -> ConduitT () Void IO [Key record] -> IO [Key record]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void IO [Key record] -> IO [Key record])
-> ConduitT () Void IO [Key record] -> IO [Key record]
forall a b. (a -> b) -> a -> b
$ ConduitM () (Key record) IO ()
src ConduitM () (Key record) IO ()
-> ConduitM (Key record) Void IO [Key record]
-> ConduitT () Void IO [Key record]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM (Key record) Void IO [Key record]
forall (m :: * -> *) a o. Monad m => ConduitT a o m [a]
CL.consume)