- class PersistField a where
- toPersistValue :: a -> PersistValue
- fromPersistValue :: PersistValue -> Either String a
- sqlType :: a -> SqlType
- isNullable :: a -> Bool
- class PersistEntity val where
- data EntityField val :: * -> *
- data Unique val :: ((* -> *) -> * -> *) -> *
- persistColumnDef :: EntityField val typ -> ColumnDef
- entityDef :: val -> EntityDef
- toPersistFields :: val -> [SomePersistField]
- fromPersistValues :: [PersistValue] -> Either String val
- halfDefined :: val
- persistUniqueToFieldNames :: Unique val backend -> [String]
- persistUniqueToValues :: Unique val backend -> [PersistValue]
- persistUniqueKeys :: val -> [Unique val backend]
- class (MonadIO (b m), MonadIO m, Monad (b m), Monad m) => PersistBackend b m where
- insert :: PersistEntity val => val -> b m (Key b val)
- replace :: PersistEntity val => Key b val -> val -> b m ()
- update :: PersistEntity val => Key b val -> [Update val] -> b m ()
- updateWhere :: PersistEntity val => [Filter val] -> [Update val] -> b m ()
- delete :: PersistEntity val => Key b val -> b m ()
- deleteBy :: PersistEntity val => Unique val b -> b m ()
- deleteWhere :: PersistEntity val => [Filter val] -> b m ()
- get :: PersistEntity val => Key b val -> b m (Maybe val)
- getBy :: PersistEntity val => Unique val b -> b m (Maybe (Key b val, val))
- selectEnum :: PersistEntity val => [Filter val] -> [SelectOpt val] -> Enumerator (Key b val, val) (b m) a
- selectFirst :: PersistEntity val => [Filter val] -> [SelectOpt val] -> b m (Maybe (Key b val, val))
- selectKeys :: PersistEntity val => [Filter val] -> Enumerator (Key b val) (b m) a
- count :: PersistEntity val => [Filter val] -> b m Int
- newtype Key backend entity = Key {}
- selectList :: (PersistEntity val, PersistBackend b m) => [Filter val] -> [SelectOpt val] -> b m [(Key b val, val)]
- insertBy :: (PersistEntity v, PersistBackend b m) => v -> b m (Either (Key b v, v) (Key b v))
- getJust :: (PersistBackend b m, PersistEntity val, Show (Key b val)) => Key b val -> b m val
- belongsTo :: (PersistBackend b m, PersistEntity ent1, PersistEntity ent2) => (ent1 -> Maybe (Key b ent2)) -> ent1 -> b m (Maybe ent2)
- belongsToJust :: (PersistBackend b m, PersistEntity ent1, PersistEntity ent2) => (ent1 -> Key b ent2) -> ent1 -> b m ent2
- getByValue :: (PersistEntity v, PersistBackend b m) => v -> b m (Maybe (Key b v, v))
- checkUnique :: (PersistEntity val, PersistBackend b m) => val -> b m Bool
- data Update v = forall typ . PersistField typ => Update {
- updateField :: EntityField v typ
- updateValue :: typ
- updateUpdate :: PersistUpdate
- data SelectOpt v
- = forall typ . Asc (EntityField v typ)
- | forall typ . Desc (EntityField v typ)
- | OffsetBy Int
- | LimitTo Int
- data Filter v
- = forall typ . PersistField typ => Filter {
- filterField :: EntityField v typ
- filterValue :: Either typ [typ]
- filterFilter :: PersistFilter
- | FilterAnd [Filter v]
- | FilterOr [Filter v]
- = forall typ . PersistField typ => Filter {
- (=.), (/=.), (*=.), (-=.), (+=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v
- (==.), (>=.), (>.), (<=.), (<.), (!=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter v
- (<-.), (/<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter v
- (||.) :: forall v. [Filter v] -> [Filter v] -> [Filter v]
Documentation
class PersistField a whereSource
A value which can be marshalled to and from a PersistValue
.
toPersistValue :: a -> PersistValueSource
fromPersistValue :: PersistValue -> Either String aSource
isNullable :: a -> BoolSource
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.
data EntityField val :: * -> *Source
Parameters: val and datatype of the field
data Unique val :: ((* -> *) -> * -> *) -> *Source
Unique keys in existence on this entity.
persistColumnDef :: EntityField val typ -> ColumnDefSource
entityDef :: val -> EntityDefSource
toPersistFields :: val -> [SomePersistField]Source
fromPersistValues :: [PersistValue] -> Either String valSource
halfDefined :: valSource
persistUniqueToFieldNames :: Unique val backend -> [String]Source
persistUniqueToValues :: Unique val backend -> [PersistValue]Source
persistUniqueKeys :: val -> [Unique val backend]Source
class (MonadIO (b m), MonadIO m, Monad (b m), Monad m) => PersistBackend b m whereSource
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 Key
s of all records matching the given criterion.
count :: PersistEntity val => [Filter val] -> b m IntSource
The total number of records fulfilling the given criterion.
newtype Key backend entity Source
Eq (Key backend entity) | |
Ord (Key backend entity) | |
Read (Key backend entity) | |
Show (Key backend entity) | |
SinglePiece (Key SqlPersist entity) | |
PersistField (Key backend entity) |
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
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
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.
checkUnique :: (PersistEntity val, PersistBackend b m) => val -> b m BoolSource
forall typ . PersistField typ => Update | |
|
forall typ . Asc (EntityField v typ) | |
forall typ . Desc (EntityField v typ) | |
OffsetBy Int | |
LimitTo Int |
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.
forall typ . PersistField typ => Filter | |
| |
FilterAnd [Filter v] | convenient for internal use, not needed for the API |
FilterOr [Filter v] |
(=.), (/=.), (*=.), (-=.), (+=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update vSource
(==.), (>=.), (>.), (<=.), (<.), (!=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Filter vSource
assign a field a value
assign a field by addition (+=)
assign a field by subtraction (-=)
assign a field by multiplication (*=)
assign a field by division (/=)
(<-.), (/<-.) :: forall v typ. PersistField typ => EntityField v typ -> [typ] -> Filter vSource