This defines the API for performing database actions. There are two levels to this API: dealing with fields, and dealing with entities. In SQL, a field corresponds to a column, and should be a single, non-composite value. An entity corresponds to a SQL table. In other words: An entity is a collection of fields.
- data PersistValue
- data SqlType
- = SqlString
- | SqlInt32
- | SqlInteger
- | SqlReal
- | SqlBool
- | SqlDay
- | SqlTime
- | SqlDayTime
- | SqlBlob
- class PersistField a where
- toPersistValue :: a -> PersistValue
- fromPersistValue :: PersistValue -> Either String a
- sqlType :: a -> SqlType
- isNullable :: a -> Bool
- class Show (Key val) => PersistEntity val where
- data Key val
- data Update val
- data Filter val
- data Order val
- data Unique val
- entityDef :: val -> EntityDef
- toPersistFields :: val -> [SomePersistField]
- fromPersistValues :: [PersistValue] -> Either String val
- halfDefined :: val
- toPersistKey :: PersistValue -> Key val
- fromPersistKey :: Key val -> PersistValue
- persistFilterToFieldName :: Filter val -> String
- persistFilterToFilter :: Filter val -> PersistFilter
- persistFilterToValue :: Filter val -> Either PersistValue [PersistValue]
- persistOrderToFieldName :: Order val -> String
- persistOrderToOrder :: Order val -> PersistOrder
- persistUpdateToFieldName :: Update val -> String
- persistUpdateToUpdate :: Update val -> PersistUpdate
- persistUpdateToValue :: Update val -> PersistValue
- persistUniqueToFieldNames :: Unique val -> [String]
- persistUniqueToValues :: Unique val -> [PersistValue]
- persistUniqueKeys :: val -> [Unique val]
- data EntityDef = EntityDef {
- entityName :: String
- entityAttribs :: [String]
- entityColumns :: [(String, String, [String])]
- entityUniques :: [(String, [String])]
- entityDerives :: [String]
- class Monad m => PersistBackend m where
- insert :: PersistEntity val => val -> m (Key val)
- replace :: PersistEntity val => Key val -> val -> m ()
- update :: PersistEntity val => Key val -> [Update val] -> m ()
- updateWhere :: PersistEntity val => [Filter val] -> [Update val] -> m ()
- delete :: PersistEntity val => Key val -> m ()
- deleteBy :: PersistEntity val => Unique val -> m ()
- deleteWhere :: PersistEntity val => [Filter val] -> m ()
- get :: PersistEntity val => Key val -> m (Maybe val)
- getBy :: PersistEntity val => Unique val -> m (Maybe (Key val, val))
- selectEnum :: PersistEntity val => [Filter val] -> [Order val] -> Int -> Int -> Enumerator (Key val, val) m a
- selectKeys :: PersistEntity val => [Filter val] -> Enumerator (Key val) m a
- count :: PersistEntity val => [Filter val] -> m Int
- data PersistFilter
- data PersistUpdate
- data PersistOrder
- data SomePersistField = forall a . PersistField a => SomePersistField a
- selectList :: (PersistEntity val, PersistBackend m, Monad m) => [Filter val] -> [Order val] -> Int -> Int -> m [(Key val, val)]
- insertBy :: (PersistEntity v, PersistBackend m) => v -> m (Either (Key v, v) (Key v))
- getByValue :: (PersistEntity v, PersistBackend m) => v -> m (Maybe (Key v, v))
- checkUnique :: (PersistEntity val, PersistBackend m) => val -> m Bool
- class PersistEntity a => DeleteCascade a where
- deleteCascade :: PersistBackend m => Key a -> m ()
- deleteCascadeWhere :: (DeleteCascade a, PersistBackend m) => [Filter a] -> m ()
- data PersistException = PersistMarshalException String
Documentation
data PersistValue Source
A raw value which can be stored in any backend and can be marshalled to
and from a PersistField
.
PersistText Text | |
PersistByteString ByteString | |
PersistInt64 Int64 | |
PersistDouble Double | |
PersistBool Bool | |
PersistDay Day | |
PersistTimeOfDay TimeOfDay | |
PersistUTCTime UTCTime | |
PersistNull | |
PersistList [PersistValue] | |
PersistMap [(Text, PersistValue)] | |
PersistForeignKey ByteString | intended especially for MongoDB backend |
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.
SqlString | |
SqlInt32 | |
SqlInteger | FIXME 8-byte integer; should be renamed SqlInt64 |
SqlReal | |
SqlBool | |
SqlDay | |
SqlTime | |
SqlDayTime | |
SqlBlob |
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 Show (Key val) => 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.
The unique identifier associated with this entity. In general, backends also define a type synonym for this, such that "type MyEntityId = Key MyEntity".
Fields which can be updated using the update
and updateWhere
functions.
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.
How you can sort the results of a select
.
Unique keys in existence on this entity.
entityDef :: val -> EntityDefSource
toPersistFields :: val -> [SomePersistField]Source
fromPersistValues :: [PersistValue] -> Either String valSource
halfDefined :: valSource
toPersistKey :: PersistValue -> Key valSource
fromPersistKey :: Key val -> PersistValueSource
persistFilterToFieldName :: Filter val -> StringSource
persistFilterToFilter :: Filter val -> PersistFilterSource
persistFilterToValue :: Filter val -> Either PersistValue [PersistValue]Source
persistOrderToFieldName :: Order val -> StringSource
persistOrderToOrder :: Order val -> PersistOrderSource
persistUpdateToFieldName :: Update val -> StringSource
persistUpdateToUpdate :: Update val -> PersistUpdateSource
persistUpdateToValue :: Update val -> PersistValueSource
persistUniqueToFieldNames :: Unique val -> [String]Source
persistUniqueToValues :: Unique val -> [PersistValue]Source
persistUniqueKeys :: val -> [Unique val]Source
EntityDef | |
|
class Monad m => PersistBackend m whereSource
insert :: PersistEntity val => val -> m (Key val)Source
Create a new record in the database, returning the newly created identifier.
replace :: PersistEntity val => Key val -> val -> 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 val -> [Update val] -> m ()Source
Update individual fields on a specific record.
updateWhere :: PersistEntity val => [Filter val] -> [Update val] -> m ()Source
Update individual fields on any record matching the given criterion.
delete :: PersistEntity val => Key val -> m ()Source
Delete a specific record by identifier. Does nothing if record does not exist.
deleteBy :: PersistEntity val => Unique val -> m ()Source
Delete a specific record by unique key. Does nothing if no record matches.
deleteWhere :: PersistEntity val => [Filter val] -> m ()Source
Delete all records matching the given criterion.
get :: PersistEntity val => Key val -> m (Maybe val)Source
Get a record by identifier, if available.
getBy :: PersistEntity val => Unique val -> m (Maybe (Key val, val))Source
Get a record by unique key, if available. Returns also the identifier.
:: PersistEntity val | |
=> [Filter val] | |
-> [Order val] | |
-> Int | limit |
-> Int | offset |
-> Enumerator (Key val, val) m a |
Get all records matching the given criterion in the specified order. Returns also the identifiers.
selectKeys :: PersistEntity val => [Filter val] -> Enumerator (Key val) m aSource
Get the Key
s of all records matching the given criterion.
count :: PersistEntity val => [Filter val] -> m IntSource
The total number of records fulfilling the given criterion.
MonadControlIO m => PersistBackend (SqlPersist m) |
data SomePersistField Source
forall a . PersistField a => SomePersistField a |
:: (PersistEntity val, PersistBackend m, Monad m) | |
=> [Filter val] | |
-> [Order val] | |
-> Int | limit |
-> Int | offset |
-> m [(Key val, val)] |
Call select
but return the result as a list.
insertBy :: (PersistEntity v, PersistBackend m) => v -> m (Either (Key v, v) (Key v))Source
getByValue :: (PersistEntity v, PersistBackend m) => v -> m (Maybe (Key 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 m) => val -> m BoolSource
class PersistEntity a => DeleteCascade a whereSource
deleteCascade :: PersistBackend m => Key a -> m ()Source
deleteCascadeWhere :: (DeleteCascade a, PersistBackend m) => [Filter a] -> m ()Source