persistent-0.6.4.4: Type-safe, non-relational, multi-backend persistence.

Database.Persist.Base

Contents

Description

API for database actions. The API deals with fields and entities. In SQL, a field corresponds to a column, and should be a single non-composite value. An entity corresponds to a SQL table, so an entity is a collection of fields.

Synopsis

Documentation

data SqlType Source

A SQL data type. Naming attempts to reflect the underlying Haskell datatypes, eg SqlString instead of SqlVarchar. Different SQL databases may have different translations for these types.

Constructors

SqlString 
SqlInt32 
SqlInteger

FIXME 8-byte integer; should be renamed SqlInt64

SqlReal 
SqlBool 
SqlDay 
SqlTime 
SqlDayTime 
SqlBlob 

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

data Unique val :: ((* -> *) -> * -> *) -> *Source

Unique keys in existence on this entity.

class (MonadIO (b m), MonadIO m, Monad (b m), Monad m) => PersistBackend b m whereSource

Methods

insert :: PersistEntity val => val -> b m (Key b val)Source

Create a new record in the database, returning the newly created identifier.

replace :: PersistEntity val => Key b val -> val -> b m ()Source

Replace the record in the database with the given key. Result is undefined if such a record does not exist.

update :: PersistEntity val => Key b val -> [Update val] -> b m ()Source

Update individual fields on a specific record.

updateWhere :: PersistEntity val => [Filter val] -> [Update val] -> b m ()Source

Update individual fields on any record matching the given criterion.

delete :: PersistEntity val => Key b val -> b m ()Source

Delete a specific record by identifier. Does nothing if record does not exist.

deleteBy :: PersistEntity val => Unique val b -> b m ()Source

Delete a specific record by unique key. Does nothing if no record matches.

deleteWhere :: PersistEntity val => [Filter val] -> b m ()Source

Delete all records matching the given criterion.

get :: PersistEntity val => Key b val -> b m (Maybe val)Source

Get a record by identifier, if available.

getBy :: PersistEntity val => Unique val b -> b m (Maybe (Key b val, val))Source

Get a record by unique key, if available. Returns also the identifier.

selectEnum :: PersistEntity val => [Filter val] -> [SelectOpt val] -> Enumerator (Key b val, val) (b m) aSource

Get all records matching the given criterion in the specified order. Returns also the identifiers.

selectFirst :: PersistEntity val => [Filter val] -> [SelectOpt val] -> b m (Maybe (Key b val, val))Source

get just the first record for the criterion

selectKeys :: PersistEntity val => [Filter val] -> Enumerator (Key b val) (b m) aSource

Get the Keys of all records matching the given criterion.

count :: PersistEntity val => [Filter val] -> b m IntSource

The total number of records fulfilling the given criterion.

data SelectOpt v Source

Constructors

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

selectList :: (PersistEntity val, PersistBackend b m) => [Filter val] -> [SelectOpt val] -> b m [(Key b val, val)]Source

Call select but return the result as a list.

insertBy :: (PersistEntity v, PersistBackend b m) => v -> b m (Either (Key b v, v) (Key b 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.

getByValue :: (PersistEntity v, PersistBackend b m) => v -> b m (Maybe (Key b v, 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.

getJust :: (PersistBackend b m, PersistEntity val, Show (Key b val)) => Key b val -> b 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 :: (PersistBackend b m, PersistEntity ent1, PersistEntity ent2) => (ent1 -> Maybe (Key b ent2)) -> ent1 -> b m (Maybe ent2)Source

belongsToJust :: (PersistBackend b m, PersistEntity ent1, PersistEntity ent2) => (ent1 -> Key b ent2) -> ent1 -> b m ent2Source

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

checkUnique :: (PersistEntity val, PersistBackend b m) => val -> b 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.

class PersistEntity a => DeleteCascade a b whereSource

Methods

deleteCascade :: PersistBackend b m => Key b a -> b m ()Source

data Update v Source

Constructors

forall typ . PersistField typ => Update 

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] 

newtype Key backend entity Source

Constructors

Key 

Fields

unKey :: PersistValue
 

Instances

Eq (Key backend entity) 
Ord (Key backend entity) 
Read (Key backend entity) 
Show (Key backend entity) 
SinglePiece (Key SqlPersist entity) 
PersistField (Key backend entity) 

Definition

data UniqueDef Source

Constructors

UniqueDef 

Instances

fst3 :: forall t t1 t2. (t, t1, t2) -> tSource

snd3 :: forall t t1 t2. (t, t1, t2) -> t1Source

third3 :: forall t t1 t2. (t, t1, t2) -> t2Source

Config

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 :: TextObject -> Either String cSource

withPool :: (Applicative m, MonadBaseControl IO m, MonadIO m) => c -> (PersistConfigPool c -> m a) -> m aSource

I really don't want Applicative here, but it's necessary for Mongo.

runPool :: (MonadBaseControl IO m, MonadIO m) => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m aSource