groundhog-0.7.0.1: Type-safe datatype-database mapping library.

Safe HaskellNone
LanguageHaskell98

Database.Groundhog

Contents

Description

This module exports the most commonly used functions and datatypes.

See http://github.com/lykahb/groundhog/blob/master/examples/.

Synopsis

Core datatypes and functions

class (Monad m, DbDescriptor (PhantomDb m)) => PersistBackend m where Source

Associated Types

type PhantomDb m Source

A token which defines the DB type. For example, different monads working with Sqlite, return may Sqlite type.

Methods

insert :: PersistEntity v => v -> m (AutoKey v) Source

Insert a new record to a database and return its autogenerated key or ()

insert_ :: PersistEntity v => v -> m () Source

Insert a new record to a database. For some backends it may be faster than insert.

insertBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u))) => u (UniqueMarker v) -> v -> m (Either (AutoKey v) (AutoKey v)) Source

Try to insert a record and return Right newkey. If there is a constraint violation for the given constraint, Left oldkey is returned , where oldkey is an identifier of the record with the matching values.

insertByAll :: PersistEntity v => v -> m (Either (AutoKey v) (AutoKey v)) Source

Try to insert a record and return Right newkey. If there is a constraint violation for any constraint, Left oldkey is returned , where oldkey is an identifier of the record with the matching values. Note that if several constraints are violated, a key of an arbitrary matching record is returned.

replace :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific)) => Key v BackendSpecific -> v -> m () Source

Replace a record with the given autogenerated key. Result is undefined if the record does not exist.

replaceBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u))) => u (UniqueMarker v) -> v -> m () Source

Replace a record. The unique key marker defines what unique key of the entity is used.

select :: (PersistEntity v, EntityConstr v c, HasSelectOptions opts (PhantomDb m) (RestrictionHolder v c)) => opts -> m [v] Source

Return a list of the records satisfying the condition. Example: select $ (FirstField ==. "abc" &&. SecondField >. "def") `orderBy` [Asc ThirdField] `limitTo` 100

selectAll :: PersistEntity v => m [(AutoKey v, v)] Source

Return a list of all records. Order is undefined. It can be useful for datatypes with multiple constructors.

get :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific)) => Key v BackendSpecific -> m (Maybe v) Source

Fetch an entity from a database

getBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u))) => Key v (Unique u) -> m (Maybe v) Source

Fetch an entity from a database by its unique key

update :: (PersistEntity v, EntityConstr v c) => [Update (PhantomDb m) (RestrictionHolder v c)] -> Cond (PhantomDb m) (RestrictionHolder v c) -> m () Source

Update the records satisfying the condition. Example: update [FirstField =. "abc"] $ FirstField ==. "def"

delete :: (PersistEntity v, EntityConstr v c) => Cond (PhantomDb m) (RestrictionHolder v c) -> m () Source

Remove the records satisfying the condition

deleteBy :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific)) => Key v BackendSpecific -> m () Source

Remove the record with given key. No-op if the record does not exist

deleteAll :: PersistEntity v => v -> m () Source

Remove all records. The entity parameter is used only for type inference.

count :: (PersistEntity v, EntityConstr v c) => Cond (PhantomDb m) (RestrictionHolder v c) -> m Int Source

Count total number of records satisfying the condition

countAll :: PersistEntity v => v -> m Int Source

Count total number of records with all constructors. The entity parameter is used only for type inference

project :: (PersistEntity v, EntityConstr v c, Projection' p (PhantomDb m) (RestrictionHolder v c) a, HasSelectOptions opts (PhantomDb m) (RestrictionHolder v c)) => p -> opts -> m [a] Source

Fetch projection of some fields. Example: project (SecondField, ThirdField) $ (FirstField ==. "abc" &&. SecondField >. "def") `orderBy` [Asc ThirdField] `offsetBy` 100

migrate :: PersistEntity v => v -> Migration m Source

Check database schema and create migrations for the entity and the entities it contains

executeRaw Source

Arguments

:: Bool

keep in cache

-> String

query

-> [PersistValue]

positional parameters

-> m () 

Execute raw query

queryRaw Source

Arguments

:: Bool

keep in cache

-> String

query

-> [PersistValue]

positional parameters

-> (RowPopper m -> m a)

results processing function

-> m a 

Execute raw query with results

insertList :: PersistField a => [a] -> m Int64 Source

getList :: PersistField a => Int64 -> m [a] Source

newtype DbPersist conn m a Source

Constructors

DbPersist 

Fields

unDbPersist :: ReaderT conn m a
 

Instances

MonadBaseControl IO m => MonadBaseControl IO (DbPersist conn m) 
MonadBase IO m => MonadBase IO (DbPersist conn m) 
MonadError e m => MonadError e (DbPersist conn m) 
Monad m => MonadReader conn (DbPersist conn m) 
MonadState s m => MonadState s (DbPersist conn m) 
MonadWriter w m => MonadWriter w (DbPersist conn m) 
MonadTrans (DbPersist conn) 
MonadTransControl (DbPersist conn) 
Monad m => Monad (DbPersist conn m) 
Functor m => Functor (DbPersist conn m) 
Applicative m => Applicative (DbPersist conn m) 
MonadLogger m => MonadLogger (DbPersist conn m) 
MonadIO m => MonadIO (DbPersist conn m) 
MonadCont m => MonadCont (DbPersist conn m) 
type StT (DbPersist conn) a = StT (ReaderT conn) a 
type StM (DbPersist conn m) a = ComposeSt (DbPersist conn) m a 

data Unique u Source

A holder for Unique constraints

data UniqueMarker v a Source

A phantom datatype to make instance head different u (UniqueMarker v)

Instances

(PersistEntity v, DbDescriptor db, IsUniqueKey k, (~) * k (Key v (Unique u)), (~) * (RestrictionHolder v c) r') => Expression db r' (u (UniqueMarker v)) 
(PersistEntity v, IsUniqueKey k, (~) * k (Key v (Unique u))) => FieldLike (u (UniqueMarker v)) k 
(PersistEntity v, IsUniqueKey k, (~) * k (Key v (Unique u))) => Assignable (u (UniqueMarker v)) k 
(PersistEntity v, IsUniqueKey k, (~) * k (Key v (Unique u))) => Projection (u (UniqueMarker v)) k 
type ProjectionDb (u (UniqueMarker v)) db = () 
type ProjectionRestriction (u (UniqueMarker v)) (RestrictionHolder v' c) = (~) * v v' 

data BackendSpecific Source

Key marked with this type can have value for any backend

extractUnique :: (IsUniqueKey uKey, uKey ~ Key v u) => v -> uKey Source

Creates value of unique key using the data extracted from the passed value

data Cond db r Source

Represents condition for a query.

Constructors

And (Cond db r) (Cond db r) 
Or (Cond db r) (Cond db r) 
Not (Cond db r) 
Compare ExprRelation (UntypedExpr db r) (UntypedExpr db r) 
CondRaw (QueryRaw db r) 
CondEmpty 

Instances

((~) * db' db, (~) * r' r) => Expression db' r' (Cond db r) 
(~) * a Bool => Projection (Cond db r) a 
(~) * db' db => HasSelectOptions (Cond db r) db' r 
type HasLimit (Cond db r) = HFalse 
type HasOffset (Cond db r) = HFalse 
type HasOrder (Cond db r) = HFalse 
type HasDistinct (Cond db r) = HFalse 
type ProjectionDb (Cond db r) db' = (~) * db db' 
type ProjectionRestriction (Cond db r) r' = (~) * r r' 

data Order db r Source

Defines sort order of a result-set

Constructors

forall a f . Projection' f db r a => Asc f 
forall a f . Projection' f db r a => Desc f 

data AutoKeyField v c where Source

It can be used in expressions like a regular field. For example, delete (AutoKeyField ==. k) or delete (AutoKeyField ==. k ||. SomeField ==. "DUPLICATE")

Constructors

AutoKeyField :: AutoKeyField v c 

Instances

(EntityConstr v c, DbDescriptor db, (~) * (RestrictionHolder v c) r') => Expression db r' (AutoKeyField v c) 
(EntityConstr v c, (~) * a (AutoKey v)) => FieldLike (AutoKeyField v c) a 
(EntityConstr v c, (~) * a (AutoKey v)) => Assignable (AutoKeyField v c) a 
(EntityConstr v c, (~) * a (AutoKey v)) => Projection (AutoKeyField v c) a 
type ProjectionDb (AutoKeyField v c) db = () 
type ProjectionRestriction (AutoKeyField v c) r = (~) * r (RestrictionHolder v c) 

(~>) :: (EntityConstr v c, FieldLike f a, DbDescriptor db, Projection' f db (RestrictionHolder v c) a, Embedded a) => f -> Selector a a' -> SubField db v c a' infixl 5 Source

Accesses fields of the embedded datatypes. For example, SomeField ==. ("abc", "def") ||. SomeField ~> Tuple2_0Selector ==. "def"

deleteByKey :: (PersistBackend m, PersistEntity v, PrimitivePersistField (Key v BackendSpecific)) => Key v BackendSpecific -> m () Source

Deprecated: Use deleteBy instead

Expressions

(=.) :: (Assignable f a', ProjectionDb f db, ProjectionRestriction f r, Expression db r b, Unifiable f b) => f -> b -> Update db r infixr 3 Source

Update field

(&&.) :: Cond db r -> Cond db r -> Cond db r infixr 3 Source

Boolean "and" operator.

(||.) :: Cond db r -> Cond db r -> Cond db r infixr 2 Source

Boolean "or" operator.

(==.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r infix 4 Source

(/=.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r infix 4 Source

(<.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r infix 4 Source

(<=.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r infix 4 Source

(>.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r infix 4 Source

(>=.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r infix 4 Source

isFieldNothing :: (Expression db r f, Projection f (Maybe a), PrimitivePersistField (Maybe a), Unifiable f (Maybe a)) => f -> Cond db r Source

This function more limited than (==.), but has better type inference. If you want to compare your value to Nothing with (==.) operator, you have to write the types explicitly myExpr ==. (Nothing :: Maybe Int). TODO: restrict db r

liftExpr :: ExpressionOf db r a a' => a -> Expr db r a' Source

Converts value to Expr. It can help to pass values of different types into functions which expect arguments of the same type, like (+).

toArith :: ExpressionOf db r a a' => a -> Expr db r a' Source

Deprecated: Please use liftExpr instead

It is kept for compatibility with older Groundhog versions and can be replaced with "liftExpr".

Migration

createMigration :: Monad m => Migration m -> m NamedMigrations Source

Produce the migrations but not execute them. Fails when an unsafe migration occurs.

executeMigration :: (PersistBackend m, MonadIO m) => NamedMigrations -> m () Source

Execute the migrations with printing to stderr. Fails when an unsafe migration occurs.

executeMigrationUnsafe :: (PersistBackend m, MonadIO m) => NamedMigrations -> m () Source

Execute migrations. Executes the unsafe migrations without warnings and prints them to stderr

runMigration :: (PersistBackend m, MonadIO m) => Migration m -> m () Source

Creates migrations and executes them with printing to stderr. Fails when an unsafe migration occurs. > runMigration m = createMigration m >>= executeMigration

runMigrationUnsafe :: (PersistBackend m, MonadIO m) => Migration m -> m () Source

Creates migrations and executes them with printing to stderr. Executes the unsafe migrations without warnings > runMigrationUnsafe m = createMigration m >>= executeMigrationUnsafe

printMigration :: MonadIO m => NamedMigrations -> m () Source

Pretty print the migrations