| Safe Haskell | None | 
|---|
Database.Persist
- module Database.Persist.Class
 - module Database.Persist.Types
 - insertBy :: (PersistEntity v, PersistStore m, PersistUnique m, PersistMonadBackend m ~ PersistEntityBackend v) => v -> m (Either (Entity v) (Key v))
 - getJust :: (PersistStore m, PersistEntity val, Show (Key val), PersistMonadBackend m ~ PersistEntityBackend val) => Key val -> m val
 - belongsTo :: (PersistStore m, PersistEntity ent1, PersistEntity ent2, PersistMonadBackend m ~ PersistEntityBackend ent2) => (ent1 -> Maybe (Key ent2)) -> ent1 -> m (Maybe ent2)
 - belongsToJust :: (PersistStore m, PersistEntity ent1, PersistEntity ent2, PersistMonadBackend m ~ PersistEntityBackend ent2) => (ent1 -> Key ent2) -> ent1 -> m ent2
 - getByValue :: (PersistEntity v, PersistUnique m, PersistEntityBackend v ~ PersistMonadBackend m) => v -> m (Maybe (Entity v))
 - selectList :: (PersistEntity val, PersistQuery m, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> m [Entity val]
 - selectKeysList :: (PersistEntity val, PersistQuery m, PersistEntityBackend val ~ PersistMonadBackend m) => [Filter val] -> [SelectOpt val] -> m [Key val]
 - deleteCascadeWhere :: (DeleteCascade a m, PersistQuery m) => [Filter a] -> m ()
 - (=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v
 - (+=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v
 - (-=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v
 - (*=.) :: forall v typ. PersistField typ => EntityField v typ -> typ -> Update v
 - (/=.) :: 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 typ. PersistField typ => EntityField v typ -> typ -> Filter 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 typ. PersistField typ => EntityField v typ -> typ -> Filter 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]
 - listToJSON :: [PersistValue] -> Text
 - mapToJSON :: [(Text, PersistValue)] -> Text
 - getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)]
 - limitOffsetOrder :: PersistEntity val => [SelectOpt val] -> (Int, Int, [SelectOpt val])
 
Documentation
module Database.Persist.Class
module Database.Persist.Types
Store functions
insertBy :: (PersistEntity v, PersistStore m, PersistUnique m, PersistMonadBackend m ~ PersistEntityBackend v) => v -> m (Either (Entity v) (Key v))Source
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.
Query functions
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.
deleteCascadeWhere :: (DeleteCascade a m, PersistQuery m) => [Filter a] -> m ()Source
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
JSON Utilities
listToJSON :: [PersistValue] -> TextSource
mapToJSON :: [(Text, PersistValue)] -> TextSource
getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)]Source
Other utililities
limitOffsetOrder :: PersistEntity val => [SelectOpt val] -> (Int, Int, [SelectOpt val])Source