Safe Haskell | None |
---|
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.
- data PersistValue
- = PersistText Text
- | PersistByteString ByteString
- | PersistInt64 Int64
- | PersistDouble Double
- | PersistBool Bool
- | PersistDay Day
- | PersistTimeOfDay TimeOfDay
- | PersistUTCTime UTCTime
- | PersistZonedTime ZT
- | PersistNull
- | PersistList [PersistValue]
- | PersistMap [(Text, PersistValue)]
- | PersistObjectId ByteString
- data SqlType
- class PersistField a where
- toPersistValue :: a -> PersistValue
- fromPersistValue :: PersistValue -> Either Text a
- sqlType :: a -> SqlType
- isNullable :: a -> Bool
- class PersistEntity val where
- data EntityField val :: * -> *
- type PersistEntityBackend val
- data Unique val
- persistFieldDef :: EntityField val typ -> FieldDef
- entityDef :: val -> EntityDef
- toPersistFields :: val -> [SomePersistField]
- fromPersistValues :: [PersistValue] -> Either Text val
- halfDefined :: val
- persistUniqueToFieldNames :: Unique val -> [(HaskellName, DBName)]
- persistUniqueToValues :: Unique val -> [PersistValue]
- persistUniqueKeys :: val -> [Unique val]
- persistIdField :: EntityField val (Key val)
- class MonadIO m => PersistStore m where
- type PersistMonadBackend m
- insert :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => val -> m (Key val)
- insert_ :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => val -> m ()
- insertKey :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()
- repsert :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()
- replace :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> val -> m ()
- delete :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> m ()
- get :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => Key val -> m (Maybe val)
- class PersistStore m => PersistUnique m where
- getBy :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => Unique val -> m (Maybe (Entity val))
- deleteBy :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => Unique val -> m ()
- insertUnique :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val) => val -> m (Maybe (Key val))
- data PersistFilter
- data SomePersistField = forall a . PersistField a => SomePersistField a
- newtype ZT = ZT ZonedTime
- insertBy :: (PersistEntity v, PersistStore m, PersistUnique m, PersistMonadBackend m ~ PersistEntityBackend v) => v -> m (Either (Entity v) (Key v))
- getByValue :: (PersistEntity v, PersistUnique m, PersistEntityBackend v ~ PersistMonadBackend m) => v -> m (Maybe (Entity 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
- checkUnique :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val, PersistUnique m) => val -> m Bool
- class (PersistStore m, PersistEntity a, PersistEntityBackend a ~ PersistMonadBackend m) => DeleteCascade a m where
- deleteCascade :: Key a -> m ()
- data PersistException
- newtype KeyBackend backend entity = Key {}
- type Key val = KeyBackend (PersistEntityBackend val) val
- data Entity entity = Entity {}
- getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)]
- listToJSON :: [PersistValue] -> Text
- mapToJSON :: [(Text, PersistValue)] -> Text
- class PersistConfig c where
- type PersistConfigBackend c :: (* -> *) -> * -> *
- type PersistConfigPool c
- loadConfig :: Value -> Parser c
- applyEnv :: c -> IO c
- createPoolConfig :: c -> IO (PersistConfigPool c)
- runPool :: (MonadBaseControl IO m, MonadIO m) => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m a
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 | |
PersistZonedTime ZT | |
PersistNull | |
PersistList [PersistValue] | |
PersistMap [(Text, PersistValue)] | |
PersistObjectId 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.
class PersistField a whereSource
A value which can be marshalled to and from a PersistValue
.
toPersistValue :: a -> PersistValueSource
fromPersistValue :: PersistValue -> Either Text 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
type PersistEntityBackend val Source
Unique keys in existence on this entity.
persistFieldDef :: EntityField val typ -> FieldDefSource
entityDef :: val -> EntityDefSource
toPersistFields :: val -> [SomePersistField]Source
fromPersistValues :: [PersistValue] -> Either Text valSource
halfDefined :: valSource
persistUniqueToFieldNames :: Unique val -> [(HaskellName, DBName)]Source
persistUniqueToValues :: Unique val -> [PersistValue]Source
persistUniqueKeys :: val -> [Unique val]Source
persistIdField :: EntityField val (Key val)Source
class MonadIO m => PersistStore m whereSource
type PersistMonadBackend m Source
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).
insert_ :: (PersistMonadBackend m ~ PersistEntityBackend val, PersistEntity val) => val -> m ()Source
Same as insert
, but doesn't return a Key
.
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
Queries against unique keys (other than the id).
Please read the general Persistent documentation to learn how to create Unique keys. SQL backends automatically create uniqueness constraints, but for MongoDB you must place a unique index on the field.
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
data PersistFilter Source
data SomePersistField Source
forall a . PersistField a => SomePersistField a |
insertBy :: (PersistEntity v, PersistStore m, PersistUnique m, PersistMonadBackend m ~ PersistEntityBackend v) => v -> m (Either (Entity v) (Key v))Source
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.
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
checkUnique :: (PersistEntityBackend val ~ PersistMonadBackend m, PersistEntity val, PersistUnique m) => val -> m BoolSource
class (PersistStore m, PersistEntity a, PersistEntityBackend a ~ PersistMonadBackend m) => DeleteCascade a m whereSource
deleteCascade :: Key a -> m ()Source
data PersistException Source
newtype KeyBackend backend entity Source
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
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.
Helpers
getPersistMap :: PersistValue -> Either Text [(Text, PersistValue)]Source
listToJSON :: [PersistValue] -> TextSource
mapToJSON :: [(Text, PersistValue)] -> TextSource
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.
type PersistConfigBackend c :: (* -> *) -> * -> *Source
type PersistConfigPool c Source
loadConfig :: Value -> Parser cSource
Load the config settings from a Value
, most likely taken from a YAML
config file.
Modify the config settings based on environment variables.
createPoolConfig :: c -> IO (PersistConfigPool c)Source
Create a new connection pool based on the given config settings.
runPool :: (MonadBaseControl IO m, MonadIO m) => c -> PersistConfigBackend c m a -> PersistConfigPool c -> m aSource
Run a database action by taking a connection from the pool.