persistent-1.3.2: Type-safe, multi-backend data serialization.

Safe HaskellNone
LanguageHaskell98

Database.Persist.Class

Contents

Synopsis

PersistStore

class MonadIO m => PersistStore m where Source

Minimal complete definition

get, insert, insertKey, repsert, replace, delete

Associated Types

type PersistMonadBackend m Source

Methods

get :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> m (Maybe val) Source

Get a record by identifier, if available.

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.

insertMany :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => [val] -> m [Key val] Source

Create multiple records in the database. SQL backends currently use the slow default implementation of mapM insert

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.

getJust :: (PersistStore m, PersistEntity val, Show (Key val), PersistMonadBackend m ~ PersistEntityBackend val) => Key val -> m val Source

Same as get, but for a non-null (not Maybe) foreign key Unsafe unless your database is enforcing that the foreign key is valid

belongsTo :: (PersistStore m, PersistEntity ent1, PersistEntity ent2, PersistMonadBackend m ~ PersistEntityBackend ent2) => (ent1 -> Maybe (Key ent2)) -> ent1 -> m (Maybe ent2) Source

curry this to make a convenience function that loads an associated model > foreign = belongsTo foeignId

belongsToJust :: (PersistStore m, PersistEntity ent1, PersistEntity ent2, PersistMonadBackend m ~ PersistEntityBackend ent2) => (ent1 -> Key ent2) -> ent1 -> m ent2 Source

same as belongsTo, but uses getJust and therefore is similarly unsafe

PersistUnique

class PersistStore m => PersistUnique m where Source

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 manually place a unique index on the field.

Some functions in this module (insertUnique, insertBy, and replaceUnique) first query the unique indexes to check for conflicts. You could instead optimistically attempt to perform the operation (e.g. replace instead of replaceUnique). However,

  • there is some fragility to trying to catch the correct exception and determing the column of failure.
  • an exception will automatically abort the current SQL transaction

Minimal complete definition

getBy, deleteBy

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

Like insert, but returns Nothing when the record couldn't be inserted because of a uniqueness constraint.

getByValue :: (PersistEntity value, PersistUnique m, PersistEntityBackend value ~ PersistMonadBackend m) => value -> m (Maybe (Entity value)) Source

A modification of getBy, which takes the PersistEntity itself instead of a Unique value. Returns a value matching one of the unique keys. This function makes the most sense on entities with a single Unique constructor.

insertBy :: (PersistEntity val, PersistUnique m, PersistEntityBackend val ~ PersistMonadBackend m) => val -> m (Either (Entity val) (Key val)) Source

Insert a value, checking for conflicts with any unique constraints. If a duplicate exists in the database, it is returned as Left. Otherwise, the new 'Key is returned as Right.

replaceUnique :: (Eq record, Eq (Unique record), PersistEntityBackend record ~ PersistMonadBackend m, PersistEntity record, PersistStore m, PersistUnique m) => Key record -> record -> m (Maybe (Unique record)) Source

Attempt to replace the record of the given key with the given new record. First query the unique fields to make sure the replacement maintains uniqueness constraints. Return Nothing if the replacement was made. If uniqueness is violated, return a Just with the Unique violation

Since 1.2.2.0

PersistQuery

class PersistStore m => PersistQuery m where Source

Minimal complete definition

update, updateWhere, deleteWhere, selectSource, selectKeys, count

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 val Source

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 Keys of all records matching the given criterion.

count :: (PersistEntity val, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> m Int Source

The total number of records fulfilling the given criterion.

selectList :: (PersistEntity val, PersistQuery m, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> m [Entity val] Source

Call selectSource but return the result as a list.

selectKeysList :: (PersistEntity val, PersistQuery m, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> m [Key val] Source

Call selectKeys but return the result as a list.

DeleteCascade

PersistEntity

class PersistEntity record where Source

Persistent serialized Haskell records to the database. A Database Entity (A row in SQL, a document in MongoDB, etc) corresponds to a Key plus a Haskell record.

For every Haskell record type stored in the database there is a corresponding PersistEntity instance. An instance of PersistEntity contains meta-data for the record. PersistEntity also helps abstract over different record types. That way the same query interface can return a PersistEntity, with each query returning different types of Haskell records.

Some advanced type system capabilities are used to make this process type-safe. Persistent users usually don't need to understand the class associated data and functions.

Associated Types

data EntityField record :: * -> * Source

An EntityField is parameterised by the Haskell record it belongs to and the additional type of that field

type PersistEntityBackend record Source

Persistent allows multiple different backends

data Unique record Source

Unique keys besided the Key

Methods

persistFieldDef :: EntityField record typ -> FieldDef SqlType Source

return meta-data for a given EntityField

entityDef :: Monad m => m record -> EntityDef SqlType Source

retrieve the EntityDef meta-data for the record

toPersistFields :: record -> [SomePersistField] Source

Get the database fields of a record

fromPersistValues :: [PersistValue] -> Either Text record Source

Convert from database values to a Haskell record

persistUniqueToFieldNames :: Unique record -> [(HaskellName, DBName)] Source

persistUniqueToValues :: Unique record -> [PersistValue] Source

persistUniqueKeys :: record -> [Unique record] Source

persistIdField :: EntityField record (Key record) Source

fieldLens :: EntityField record field -> forall f. Functor f => (field -> f field) -> Entity record -> f (Entity record) Source

PersistField

PersistConfig

class PersistConfig c where Source

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.

Minimal complete definition

loadConfig, createPoolConfig, runPool

Associated Types

type PersistConfigBackend c :: (* -> *) -> * -> * Source

type PersistConfigPool c Source

Methods

loadConfig :: Value -> Parser c Source

Load the config settings from a Value, most likely taken from a YAML config file.

applyEnv :: c -> IO c Source

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 a Source

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) 

JSON utilities

keyValueEntityToJSON :: ToJSON e => Entity e -> Value Source

Predefined toJSON. The resulting JSON looks like {"key": 1, "value": {"name": ...}}.

The typical usage is:

  instance ToJSON User where
      toJSON = keyValueEntityToJSON

keyValueEntityFromJSON :: FromJSON e => Value -> Parser (Entity e) Source

Predefined parseJSON. The input JSON looks like {"key": 1, "value": {"name": ...}}.

The typical usage is:

  instance FromJSON User where
      parseJSON = keyValueEntityFromJSON

entityIdToJSON :: ToJSON e => Entity e -> Value Source

Predefined toJSON. The resulting JSON looks like {"id": 1, "name": ...}.

The typical usage is:

  instance ToJSON User where
      toJSON = entityIdToJSON

entityIdFromJSON :: FromJSON e => Value -> Parser (Entity e) Source

Predefined parseJSON. The input JSON looks like {"id": 1, "name": ...}.

The typical usage is:

  instance FromJSON User where
      parseJSON = entityIdFromJSON