Safe Haskell | None |
---|---|
Language | Haskell2010 |
Defines the SqlQueryRep
data type that contains a constructor corresponding
to a persistent
function.
This file is autogenerated, to keep it in sync with
Database.Persist.Monad.Shim
.
Synopsis
- data SqlQueryRep record a where
- Get :: PersistRecordBackend record SqlBackend => Key record -> SqlQueryRep record (Maybe record)
- GetMany :: PersistRecordBackend record SqlBackend => [Key record] -> SqlQueryRep record (Map (Key record) record)
- GetJust :: PersistRecordBackend record SqlBackend => Key record -> SqlQueryRep record record
- GetJustEntity :: PersistRecordBackend record SqlBackend => Key record -> SqlQueryRep record (Entity record)
- GetEntity :: PersistRecordBackend record SqlBackend => Key record -> SqlQueryRep record (Maybe (Entity record))
- BelongsTo :: (PersistEntity record1, PersistRecordBackend record2 SqlBackend) => (record1 -> Maybe (Key record2)) -> record1 -> SqlQueryRep (record1, record2) (Maybe record2)
- BelongsToJust :: (PersistEntity record1, PersistRecordBackend record2 SqlBackend) => (record1 -> Key record2) -> record1 -> SqlQueryRep (record1, record2) record2
- Insert :: PersistRecordBackend record SqlBackend => record -> SqlQueryRep record (Key record)
- Insert_ :: PersistRecordBackend record SqlBackend => record -> SqlQueryRep record ()
- InsertMany :: PersistRecordBackend record SqlBackend => [record] -> SqlQueryRep record [Key record]
- InsertMany_ :: PersistRecordBackend record SqlBackend => [record] -> SqlQueryRep record ()
- InsertEntityMany :: PersistRecordBackend record SqlBackend => [Entity record] -> SqlQueryRep record ()
- InsertKey :: PersistRecordBackend record SqlBackend => Key record -> record -> SqlQueryRep record ()
- Repsert :: PersistRecordBackend record SqlBackend => Key record -> record -> SqlQueryRep record ()
- RepsertMany :: PersistRecordBackend record SqlBackend => [(Key record, record)] -> SqlQueryRep record ()
- Replace :: PersistRecordBackend record SqlBackend => Key record -> record -> SqlQueryRep record ()
- Delete :: PersistRecordBackend record SqlBackend => Key record -> SqlQueryRep record ()
- Update :: PersistRecordBackend record SqlBackend => Key record -> [Update record] -> SqlQueryRep record ()
- UpdateGet :: PersistRecordBackend record SqlBackend => Key record -> [Update record] -> SqlQueryRep record record
- InsertEntity :: PersistRecordBackend record SqlBackend => record -> SqlQueryRep record (Entity record)
- InsertRecord :: PersistRecordBackend record SqlBackend => record -> SqlQueryRep record record
- GetBy :: PersistRecordBackend record SqlBackend => Unique record -> SqlQueryRep record (Maybe (Entity record))
- GetByValue :: (PersistRecordBackend record SqlBackend, AtLeastOneUniqueKey record) => record -> SqlQueryRep record (Maybe (Entity record))
- CheckUnique :: PersistRecordBackend record SqlBackend => record -> SqlQueryRep record (Maybe (Unique record))
- CheckUniqueUpdateable :: PersistRecordBackend record SqlBackend => Entity record -> SqlQueryRep record (Maybe (Unique record))
- DeleteBy :: PersistRecordBackend record SqlBackend => Unique record -> SqlQueryRep record ()
- InsertUnique :: PersistRecordBackend record SqlBackend => record -> SqlQueryRep record (Maybe (Key record))
- Upsert :: (PersistRecordBackend record SqlBackend, OnlyOneUniqueKey record) => record -> [Update record] -> SqlQueryRep record (Entity record)
- UpsertBy :: PersistRecordBackend record SqlBackend => Unique record -> record -> [Update record] -> SqlQueryRep record (Entity record)
- PutMany :: PersistRecordBackend record SqlBackend => [record] -> SqlQueryRep record ()
- InsertBy :: (PersistRecordBackend record SqlBackend, AtLeastOneUniqueKey record) => record -> SqlQueryRep record (Either (Entity record) (Key record))
- InsertUniqueEntity :: PersistRecordBackend record SqlBackend => record -> SqlQueryRep record (Maybe (Entity record))
- ReplaceUnique :: (PersistRecordBackend record SqlBackend, Eq (Unique record), Eq record) => Key record -> record -> SqlQueryRep record (Maybe (Unique record))
- OnlyUnique :: (PersistRecordBackend record SqlBackend, OnlyOneUniqueKey record) => record -> SqlQueryRep record (Unique record)
- SelectSourceRes :: (MonadIO m2, PersistRecordBackend record SqlBackend) => [Filter record] -> [SelectOpt record] -> SqlQueryRep record (Acquire (ConduitM () (Entity record) m2 ()))
- SelectFirst :: PersistRecordBackend record SqlBackend => [Filter record] -> [SelectOpt record] -> SqlQueryRep record (Maybe (Entity record))
- SelectKeysRes :: (MonadIO m2, PersistRecordBackend record SqlBackend) => [Filter record] -> [SelectOpt record] -> SqlQueryRep record (Acquire (ConduitM () (Key record) m2 ()))
- Count :: PersistRecordBackend record SqlBackend => [Filter record] -> SqlQueryRep record Int
- Exists :: PersistRecordBackend record SqlBackend => [Filter record] -> SqlQueryRep record Bool
- SelectList :: PersistRecordBackend record SqlBackend => [Filter record] -> [SelectOpt record] -> SqlQueryRep record [Entity record]
- SelectKeysList :: PersistRecordBackend record SqlBackend => [Filter record] -> [SelectOpt record] -> SqlQueryRep record [Key record]
- UpdateWhere :: PersistRecordBackend record SqlBackend => [Filter record] -> [Update record] -> SqlQueryRep record ()
- DeleteWhere :: PersistRecordBackend record SqlBackend => [Filter record] -> SqlQueryRep record ()
- DeleteWhereCount :: PersistRecordBackend record SqlBackend => [Filter record] -> SqlQueryRep record Int64
- UpdateWhereCount :: PersistRecordBackend record SqlBackend => [Filter record] -> [Update record] -> SqlQueryRep record Int64
- ParseMigration :: HasCallStack => Migration -> SqlQueryRep Void (Either [Text] CautiousMigration)
- ParseMigration' :: HasCallStack => Migration -> SqlQueryRep Void CautiousMigration
- PrintMigration :: HasCallStack => Migration -> SqlQueryRep Void ()
- ShowMigration :: HasCallStack => Migration -> SqlQueryRep Void [Text]
- GetMigration :: HasCallStack => Migration -> SqlQueryRep Void [Sql]
- RunMigration :: Migration -> SqlQueryRep Void ()
- RunMigrationQuiet :: Migration -> SqlQueryRep Void [Text]
- RunMigrationSilent :: Migration -> SqlQueryRep Void [Text]
- RunMigrationUnsafe :: Migration -> SqlQueryRep Void ()
- RunMigrationUnsafeQuiet :: HasCallStack => Migration -> SqlQueryRep Void [Text]
- GetFieldName :: PersistRecordBackend record SqlBackend => EntityField record typ -> SqlQueryRep record Text
- GetTableName :: PersistRecordBackend record SqlBackend => record -> SqlQueryRep record Text
- WithRawQuery :: Text -> [PersistValue] -> ConduitM [PersistValue] Void IO a -> SqlQueryRep Void a
- RawQueryRes :: MonadIO m2 => Text -> [PersistValue] -> SqlQueryRep Void (Acquire (ConduitM () [PersistValue] m2 ()))
- RawExecute :: Text -> [PersistValue] -> SqlQueryRep Void ()
- RawExecuteCount :: Text -> [PersistValue] -> SqlQueryRep Void Int64
- RawSql :: RawSql a => Text -> [PersistValue] -> SqlQueryRep Void [a]
- TransactionSave :: SqlQueryRep Void ()
- TransactionSaveWithIsolation :: IsolationLevel -> SqlQueryRep Void ()
- TransactionUndo :: SqlQueryRep Void ()
- TransactionUndoWithIsolation :: IsolationLevel -> SqlQueryRep Void ()
- UnsafeLiftSql :: Text -> (forall m. MonadIO m => SqlPersistT m a) -> SqlQueryRep Void a
- runSqlQueryRep :: MonadUnliftIO m => SqlQueryRep record a -> SqlPersistT m a
Documentation
data SqlQueryRep record a where Source #
The data type containing a constructor for each persistent function we'd
like to lift into MonadSqlQuery
.
The record
type parameter contains the PersistEntity
types used in a
given function.
We're using a free-monads-like technique here to allow us to introspect
persistent functions in MonadSqlQuery
, e.g. to
mock out persistent calls in tests.
Instances
Typeable record => Show (SqlQueryRep record a) Source # | |
Defined in Database.Persist.Monad.SqlQueryRep showsPrec :: Int -> SqlQueryRep record a -> ShowS # show :: SqlQueryRep record a -> String # showList :: [SqlQueryRep record a] -> ShowS # |
runSqlQueryRep :: MonadUnliftIO m => SqlQueryRep record a -> SqlPersistT m a Source #
A helper to execute the actual persistent
function corresponding to
each SqlQueryRep
data constructor.