Safe Haskell | None |
---|
Database.Persist.Class
- class (PersistStore m, PersistEntity a, PersistEntityBackend a ~ PersistMonadBackend m) => DeleteCascade a m where
- deleteCascade :: Key a -> m ()
- class PersistEntity val where
- data EntityField val :: * -> *
- type PersistEntityBackend val
- data Unique val
- persistFieldDef :: EntityField val typ -> FieldDef SqlType
- entityDef :: Monad m => m val -> EntityDef SqlType
- toPersistFields :: val -> [SomePersistField]
- fromPersistValues :: [PersistValue] -> Either Text val
- persistUniqueToFieldNames :: Unique val -> [(HaskellName, DBName)]
- persistUniqueToValues :: Unique val -> [PersistValue]
- persistUniqueKeys :: val -> [Unique val]
- persistIdField :: EntityField val (Key val)
- fieldLens :: EntityField val field -> forall f. Functor f => (field -> f field) -> Entity val -> f (Entity val)
- class PersistStore m => PersistQuery m where
- update :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => Key val -> [Update val] -> m ()
- updateGet :: (PersistEntity val, PersistMonadBackend m ~ PersistEntityBackend val) => Key val -> [Update val] -> m val
- updateWhere :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [Update val] -> m ()
- deleteWhere :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> m ()
- selectSource :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> Source m (Entity val)
- selectFirst :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> m (Maybe (Entity val))
- selectKeys :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> Source m (Key val)
- count :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> m Int
- class PersistStore m => PersistUnique m where
- getBy :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => Unique val -> m (Maybe (Entity val))
- deleteBy :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => Unique val -> m ()
- insertUnique :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => val -> m (Maybe (Key val))
- class PersistConfig c where
- type PersistConfigBackend c :: (* -> *) -> * -> *
- type PersistConfigPool c
- loadConfig :: Value -> Parser c
- applyEnv :: c -> IO c
- createPoolConfig :: c -> IO (PersistConfigPool c)
- runPool :: (MonadBaseControl IO m, MonadIO m) => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a
- class PersistField a where
- toPersistValue :: a -> PersistValue
- fromPersistValue :: PersistValue -> Either Text a
- class MonadIO m => PersistStore m where
- type PersistMonadBackend m
- insert :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => val -> m (Key val)
- insert_ :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => val -> m ()
- insertKey :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()
- repsert :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()
- replace :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()
- delete :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> m ()
- get :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> m (Maybe val)
Documentation
class (PersistStore m, PersistEntity a, PersistEntityBackend a ~ PersistMonadBackend m) => DeleteCascade a m whereSource
Methods
deleteCascade :: Key a -> m ()Source
class PersistEntity val whereSource
A single database entity. For example, if writing a blog application, a blog entry would be an entry, containing fields such as title and content.
Associated Types
data EntityField val :: * -> *Source
Parameters: val and datatype of the field
type PersistEntityBackend val Source
Unique keys in existence on this entity.
Methods
persistFieldDef :: EntityField val typ -> FieldDef SqlTypeSource
entityDef :: Monad m => m val -> EntityDef SqlTypeSource
toPersistFields :: val -> [SomePersistField]Source
fromPersistValues :: [PersistValue] -> Either Text valSource
persistUniqueToFieldNames :: Unique val -> [(HaskellName, DBName)]Source
persistUniqueToValues :: Unique val -> [PersistValue]Source
persistUniqueKeys :: val -> [Unique val]Source
persistIdField :: EntityField val (Key val)Source
fieldLens :: EntityField val field -> forall f. Functor f => (field -> f field) -> Entity val -> f (Entity val)Source
class PersistStore m => PersistQuery m whereSource
Methods
update :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => Key val -> [Update val] -> m ()Source
Update individual fields on a specific record.
updateGet :: (PersistEntity val, PersistMonadBackend m ~ PersistEntityBackend val) => Key val -> [Update val] -> m valSource
Update individual fields on a specific record, and retrieve the updated value from the database.
Note that this function will throw an exception if the given key is not found in the database.
updateWhere :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [Update val] -> m ()Source
Update individual fields on any record matching the given criterion.
deleteWhere :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> m ()Source
Delete all records matching the given criterion.
selectSource :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> Source m (Entity val)Source
Get all records matching the given criterion in the specified order. Returns also the identifiers.
selectFirst :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> m (Maybe (Entity val))Source
get just the first record for the criterion
selectKeys :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> Source m (Key val)Source
Get the Key
s of all records matching the given criterion.
count :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> m IntSource
The total number of records fulfilling the given criterion.
Instances
PersistQuery m => PersistQuery (ResourceT m) | |
PersistQuery m => PersistQuery (LoggingT m) | |
PersistQuery m => PersistQuery (ListT m) | |
PersistQuery m => PersistQuery (MaybeT m) | |
PersistQuery m => PersistQuery (IdentityT m) | |
(MonadResource m, MonadLogger m) => PersistQuery (SqlPersistT m) | |
PersistQuery m => PersistQuery (ContT r m) | |
(Error e, PersistQuery m) => PersistQuery (ErrorT e m) | |
PersistQuery m => PersistQuery (ReaderT r m) | |
PersistQuery m => PersistQuery (StateT s m) | |
PersistQuery m => PersistQuery (StateT s m) | |
(Monoid w, PersistQuery m) => PersistQuery (WriterT w m) | |
(Monoid w, PersistQuery m) => PersistQuery (WriterT w m) | |
PersistQuery m => PersistQuery (ConduitM i o m) | |
(Monoid w, PersistQuery m) => PersistQuery (RWST r w s m) | |
(Monoid w, PersistQuery m) => PersistQuery (RWST r w s m) | |
PersistQuery m => PersistQuery (Pipe l i o u m) |
class PersistStore m => PersistUnique m whereSource
Queries against unique keys (other than the id).
Please read the general Persistent documentation to learn how to create Unique keys. SQL backends automatically create uniqueness constraints, but for MongoDB you must place a unique index on the field.
Methods
getBy :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => Unique val -> m (Maybe (Entity val))Source
Get a record by unique key, if available. Returns also the identifier.
deleteBy :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => Unique val -> m ()Source
Delete a specific record by unique key. Does nothing if no record matches.
insertUnique :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => val -> m (Maybe (Key val))Source
Instances
PersistUnique m => PersistUnique (ResourceT m) | |
PersistUnique m => PersistUnique (LoggingT m) | |
PersistUnique m => PersistUnique (ListT m) | |
PersistUnique m => PersistUnique (MaybeT m) | |
PersistUnique m => PersistUnique (IdentityT m) | |
(MonadResource m, MonadLogger m) => PersistUnique (SqlPersistT m) | |
PersistUnique m => PersistUnique (ContT r m) | |
(Error e, PersistUnique m) => PersistUnique (ErrorT e m) | |
PersistUnique m => PersistUnique (ReaderT r m) | |
PersistUnique m => PersistUnique (StateT s m) | |
PersistUnique m => PersistUnique (StateT s m) | |
(Monoid w, PersistUnique m) => PersistUnique (WriterT w m) | |
(Monoid w, PersistUnique m) => PersistUnique (WriterT w m) | |
(Monoid w, PersistUnique m) => PersistUnique (RWST r w s m) | |
(Monoid w, PersistUnique m) => PersistUnique (RWST r w s m) | |
PersistUnique m => PersistUnique (Pipe l i o u m) |
class PersistConfig c whereSource
Represents a value containing all the configuration options for a specific backend. This abstraction makes it easier to write code that can easily swap backends.
Associated Types
type PersistConfigBackend c :: (* -> *) -> * -> *Source
type PersistConfigPool c Source
Methods
loadConfig :: Value -> Parser cSource
Load the config settings from a Value
, most likely taken from a YAML
config file.
Modify the config settings based on environment variables.
createPoolConfig :: c -> IO (PersistConfigPool c)Source
Create a new connection pool based on the given config settings.
runPool :: (MonadBaseControl IO m, MonadIO m) => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m aSource
Run a database action by taking a connection from the pool.
Instances
(PersistConfig c1, PersistConfig c2, ~ * (PersistConfigPool c1) (PersistConfigPool c2), ~ ((* -> *) -> * -> *) (PersistConfigBackend c1) (PersistConfigBackend c2)) => PersistConfig (Either c1 c2) |
class PersistField a whereSource
A value which can be marshalled to and from a PersistValue
.
Methods
toPersistValue :: a -> PersistValueSource
fromPersistValue :: PersistValue -> Either Text aSource
Instances
class MonadIO m => PersistStore m whereSource
Associated Types
type PersistMonadBackend m Source
Methods
insert :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => val -> m (Key val)Source
Create a new record in the database, returning an automatically created key (in SQL an auto-increment id).
insert_ :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => val -> m ()Source
Same as insert
, but doesn't return a Key
.
insertKey :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()Source
Create a new record in the database using the given key.
repsert :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()Source
Put the record in the database with the given key.
Unlike replace
, if a record with the given key does not
exist then a new record will be inserted.
replace :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()Source
Replace the record in the database with the given
key. Note that the result is undefined if such record does
not exist, so you must use 'insertKey or repsert
in
these cases.
delete :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> m ()Source
Delete a specific record by identifier. Does nothing if record does not exist.
get :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> m (Maybe val)Source
Get a record by identifier, if available.
Instances
PersistStore m => PersistStore (ResourceT m) | |
PersistStore m => PersistStore (LoggingT m) | |
PersistStore m => PersistStore (ListT m) | |
PersistStore m => PersistStore (MaybeT m) | |
PersistStore m => PersistStore (IdentityT m) | |
(MonadResource m, MonadLogger m) => PersistStore (SqlPersistT m) | |
PersistStore m => PersistStore (ContT r m) | |
(Error e, PersistStore m) => PersistStore (ErrorT e m) | |
PersistStore m => PersistStore (ReaderT r m) | |
PersistStore m => PersistStore (StateT s m) | |
PersistStore m => PersistStore (StateT s m) | |
(Monoid w, PersistStore m) => PersistStore (WriterT w m) | |
(Monoid w, PersistStore m) => PersistStore (WriterT w m) | |
PersistStore m => PersistStore (ConduitM i o m) | |
(Monoid w, PersistStore m) => PersistStore (RWST r w s m) | |
(Monoid w, PersistStore m) => PersistStore (RWST r w s m) | |
PersistStore m => PersistStore (Pipe l i o u m) |