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

Safe HaskellNone

Database.Persist

Contents

Synopsis

Documentation

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

data Unique val Source

Unique keys in existence on this entity.

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).

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.

class PersistStore m => PersistUnique m whereSource

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.

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 Keys 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.

newtype KeyBackend backend entity Source

Constructors

Key 

Fields

unKey :: PersistValue
 

Instances

Eq (KeyBackend backend entity) 
Eq (KeyBackend backend entity) => Ord (KeyBackend backend entity) 
Read (KeyBackend backend entity) 
Show (KeyBackend backend entity) 
ToJSON (KeyBackend backend entity) 
FromJSON (KeyBackend backend entity) 
PathPiece (KeyBackend SqlBackend entity) 
PersistField (KeyBackend backend entity) 

type Key val = KeyBackend (PersistEntityBackend val) valSource

Helper wrapper, equivalent to Key (PersistEntityBackend val) val.

Since 1.1.0

data Entity entity Source

Datatype that represents an entity, with both its key and its Haskell representation.

When using the an SQL-based backend (such as SQLite or PostgreSQL), an Entity may take any number of columns depending on how many fields it has. In order to reconstruct your entity on the Haskell side, persistent needs all of your entity columns and in the right order. Note that you don't need to worry about this when using persistent's API since everything is handled correctly behind the scenes.

However, if you want to issue a raw SQL command that returns an Entity, then you have to be careful with the column order. While you could use SELECT Entity.* WHERE ... and that would work most of the time, there are times when the order of the columns on your database is different from the order that persistent expects (for example, if you add a new field in the middle of you entity definition and then use the migration code -- persistent will expect the column to be in the middle, but your DBMS will put it as the last column). So, instead of using a query like the one above, you may use rawSql (from the Database.Persist.GenericSql module) with its /entity selection placeholder/ (a double question mark ??). Using rawSql the query above must be written as SELECT ?? WHERE ... Then rawSql will replace ?? with the list of all columns that we need from your entity in the right order. If your query returns two entities (i.e. (Entity backend a, Entity backend b)), then you must you use SELECT ??, ?? WHERE ..., and so on.

Constructors

Entity 

Fields

entityKey :: Key entity
 
entityVal :: entity
 

Instances

Eq entity => Eq (Entity entity) 
(Eq (Entity entity), Ord entity) => Ord (Entity entity) 
Read entity => Read (Entity entity) 
Show entity => Show (Entity entity) 
PersistEntity a => RawSql (Entity a) 

insertBy :: (PersistEntity v, PersistStore m, PersistUnique m, PersistMonadBackend m ~ PersistEntityBackend v) => v -> m (Either (Entity v) (Key v))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.

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

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

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

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

getByValue :: (PersistEntity v, PersistUnique m, PersistEntityBackend v ~ PersistMonadBackend m) => v -> m (Maybe (Entity v))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.

checkUnique :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val, PersistUnique m) => val -> m BoolSource

Check whether there are any conflicts for unique keys with this entity and existing entities in the database.

Returns True if the entity would be unique, and could thus safely be inserted; returns False on a conflict.

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.

data SelectOpt v Source

Constructors

forall typ . Asc (EntityField v typ) 
forall typ . Desc (EntityField v typ) 
OffsetBy Int 
LimitTo Int 

data Filter v Source

Filters which are available for select, updateWhere and deleteWhere. Each filter constructor specifies the field being filtered on, the type of comparison applied (equals, not equals, etc) and the argument for the comparison.

Constructors

forall typ . PersistField typ => Filter 
FilterAnd [Filter v]

convenient for internal use, not needed for the API

FilterOr [Filter v] 
BackendFilter (BackendSpecificFilter (PersistEntityBackend v) v) 

query combinators

(=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update vSource

assign a field a value

(+=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update vSource

assign a field by addition (+=)

(-=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update vSource

assign a field by subtraction (-=)

(*=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update vSource

assign a field by multiplication (*=)

(/=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update vSource

assign a field by division (/=)

(==.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter vSource

(!=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter vSource

(<.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter vSource

(>.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter vSource

(<=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter vSource

(>=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter vSource

(<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter vSource

In

(/<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter vSource

NotIn

(||.) :: forall v. [Filter v] -> [Filter v] -> [Filter v]Source

the OR of two lists of filters