groundhog-0.1.0.1: Type-safe ADT-database mapping library.

Safe HaskellNone

Database.Groundhog.Core

Contents

Description

This module defines the functions and datatypes used throughout the framework. Most of them are for the internal use

Synopsis

Main types

class (PersistField v, PurePersistField (AutoKey v)) => PersistEntity v whereSource

Only instances of this class can be persisted in a database

Associated Types

data Field v :: ((* -> *) -> *) -> * -> *Source

This type is used for typesafe manipulation of separate fields of datatype v. Each constructor in Field corresponds to its field in a datatype v. It is parametrised by constructor phantom type and field value type.

data Key v :: * -> *Source

A unique identifier of a value stored in a database. This may be a primary key, a constraint or unique indices. The second parameter is the key description.

type AutoKey v Source

This type is the default autoincremented key for the entity. If entity does not have such key, AutoKey v = ().

type DefaultKey v Source

This type is the default key for the entity.

Methods

entityDef :: v -> EntityDefSource

Returns a complete description of the type

toEntityPersistValues :: PersistBackend m => v -> m ([PersistValue] -> [PersistValue])Source

Marshalls value to a list of PersistValue ready for insert to a database

fromEntityPersistValues :: PersistBackend m => [PersistValue] -> m (v, [PersistValue])Source

Constructs the value from the list of PersistValue

getUniques :: DbDescriptor db => Proxy db -> v -> (Int, [(String, [PersistValue])])Source

Returns constructor number and a list of uniques names and corresponding field values

entityFieldChain :: Field v c a -> FieldChainSource

Is internally used by FieldLike Field instance We could avoid this function if class FieldLike allowed FieldLike Fields Data or FieldLike (Fields Data). However that would require additional extensions in user-space code

class PersistField a whereSource

Represents everything which can be put into a database. This data can be stored in multiple columns and tables. To get value of those columns we might need to access another table. That is why the result type is monadic.

Methods

persistName :: a -> StringSource

Return name of the type. If it is polymorhic, the names of parameter types are separated with delim symbol

toPersistValues :: PersistBackend m => a -> m ([PersistValue] -> [PersistValue])Source

Convert a value into something which can be stored in a database column. Note that for complex datatypes it may insert them to return identifier

fromPersistValues :: PersistBackend m => [PersistValue] -> m (a, [PersistValue])Source

Constructs a value from a PersistValue. For complex datatypes it may query the database

dbType :: a -> DbTypeSource

Description of value type

class PersistField a => SinglePersistField a whereSource

Represents all datatypes that map into a single column. Getting value for that column might require monadic actions to access other tables.

class PersistField v => Embedded v whereSource

Associated Types

data Selector v :: * -> *Source

Methods

selectorNum :: Selector v a -> IntSource

Instances

(PersistField (a', b'), PersistField a', PersistField b') => Embedded (a', b') 
(PersistField (a', b', c'), PersistField a', PersistField b', PersistField c') => Embedded (a', b', c') 
(PersistField (a', b', c', d'), PersistField a', PersistField b', PersistField c', PersistField d') => Embedded (a', b', c', d') 
(PersistField (a', b', c', d', e'), PersistField a', PersistField b', PersistField c', PersistField d', PersistField e') => Embedded (a', b', c', d', e') 

class Projection p r a | p -> r a whereSource

Any data that can be fetched from a database

Methods

projectionFieldChains :: p -> [FieldChain] -> [FieldChain]Source

It is like a fieldChain for many fields. Difflist is used for concatenation efficiency.

projectionResult :: PersistBackend m => p -> [PersistValue] -> m (a, [PersistValue])Source

It is like fromPersistValues. However, we cannot use it for projections in all cases. For the PersistEntity instances fromPersistValues expects entity id instead of the entity values.

Instances

(PersistEntity v, IsUniqueKey (Key v (Unique u)), ~ * r (RestrictionHolder v (UniqueConstr (Key v (Unique u))))) => Projection (u (UniqueMarker v)) r (Key v (Unique u)) 
(PersistEntity v, Constructor c) => Projection (c (ConstructorMarker v)) (RestrictionHolder v c) v 
(Projection a1 r a1', Projection a2 r a2') => Projection (a1, a2) r (a1', a2') 
(PersistEntity v, Constructor c, PersistField (Key v BackendSpecific)) => Projection (AutoKeyField v c) (RestrictionHolder v c) (Key v BackendSpecific) 
(Projection a1 r a1', Projection a2 r a2', Projection a3 r a3') => Projection (a1, a2, a3) r (a1', a2', a3') 
(PersistEntity v, Constructor c, PersistField a) => Projection (SubField v c a) (RestrictionHolder v c) a 
(PersistEntity v, Constructor c, PersistField a) => Projection (Field v c a) (RestrictionHolder v c) a 
(Projection a1 r a1', Projection a2 r a2', Projection a3 r a3', Projection a4 r a4') => Projection (a1, a2, a3, a4) r (a1', a2', a3', a4') 
(Projection a1 r a1', Projection a2 r a2', Projection a3 r a3', Projection a4 r a4', Projection a5 r a5') => Projection (a1, a2, a3, a4, a5) r (a1', a2', a3', a4', a5') 

data Unique u Source

A holder for Unique constraints

Instances

(PersistEntity v, IsUniqueKey (Key v (Unique u)), ~ * r (RestrictionHolder v (UniqueConstr (Key v (Unique u))))) => Projection (u (UniqueMarker v)) r (Key v (Unique u)) 

data KeyForBackend db v Source

A holder for DB type in backend-specific keys

Constructors

(DbDescriptor db, PersistEntity v) => KeyForBackend (AutoKeyType db) 

data BackendSpecific Source

Key marked with this type can have value for any backend

data ConstructorMarker v a Source

A phantom datatype to make instance head diffirent c (ConstructorMarker, v)

data UniqueMarker v a Source

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

Instances

~ * r (HFalse, Key v (Unique u)) => ExtractValue (u (UniqueMarker v)) r 
(PersistEntity v, IsUniqueKey (Key v (Unique u)), Projection (u (UniqueMarker v)) r a') => FieldLike (u (UniqueMarker v)) r a' 
(PersistEntity v, Constructor c, FieldLike (u (UniqueMarker v)) (RestrictionHolder v c) a', ~ ((* -> *) -> *) c' (UniqueConstr (Key v' (Unique u))), ~ * v v', IsUniqueKey (Key v' (Unique u)), ~ ((* -> *) -> *) c c') => Expression (u (UniqueMarker v)) v' c' 
(PersistEntity v, IsUniqueKey (Key v (Unique u)), ~ * r (RestrictionHolder v (UniqueConstr (Key v (Unique u))))) => Projection (u (UniqueMarker v)) r (Key v (Unique u)) 

data Proxy a Source

data HFalse Source

Instances

NormalizeValue' t (isPlain, r) => NormalizeValue HFalse HTrue t (isPlain, r) 
NormalizeValue' t (isPlain, r) => NormalizeValue HFalse HFalse t (HFalse, r) 

data HTrue Source

Instances

TypeEq x x HTrue 
~ * r (isPlain, t) => NormalizeValue HTrue isPlain t r 
NormalizeValue' t (isPlain, r) => NormalizeValue HFalse HTrue t (isPlain, r) 

newtype ZT Source

Avoid orphan instances.

Constructors

ZT ZonedTime 

Instances

Constructing expressions

data Cond v c Source

Represents condition for a query.

Constructors

And (Cond v c) (Cond v c) 
Or (Cond v c) (Cond v c) 
Not (Cond v c) 
forall a b . Compare ExprRelation (Expr v c a) (Expr v c b) 

Instances

data ExprRelation Source

Constructors

Eq 
Ne 
Gt 
Lt 
Ge 
Le 

Instances

data Update v c Source

Constructors

forall f a b . FieldLike f (RestrictionHolder v c) a => Update f (Expr v c b) 

(~>) :: (PersistEntity v, Constructor c, FieldLike f (RestrictionHolder v c) a, Embedded a) => f -> Selector a a' -> SubField v c a'Source

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

toArith :: (PersistEntity v, FieldLike f (RestrictionHolder v c) a') => f -> Arith v c a'Source

Convert field to an arithmetic value

class Projection f r a => FieldLike f r a | f -> r a whereSource

Generalises data that can occur in expressions (so far there are Field and SubField).

Methods

fieldChain :: f -> FieldChainSource

It is used to map field to column names. It can be either a column name for a regular field of non-embedded type or a list of this field and the outer fields in reverse order. Eg, fieldChain $ SomeField ~> Tuple2_0Selector may result in Right [("val0", DbString), ("some", DbEmbedded False [dbType "", dbType True])]. Function fieldChain can be simplified to f v c a -> [(String, DbType)]. Datatype Either is used for optimisation of the common case, eg Field v c Int.

Instances

(PersistEntity v, IsUniqueKey (Key v (Unique u)), Projection (u (UniqueMarker v)) r a') => FieldLike (u (UniqueMarker v)) r a' 
(PersistEntity v, Constructor c, Projection (AutoKeyField v c) r a') => FieldLike (AutoKeyField v c) r a' 
(PersistEntity v, Constructor c, Projection (SubField v c a) r a') => FieldLike (SubField v c a) r a' 
(PersistEntity v, Constructor c, Projection (Field v c a) r a') => FieldLike (Field v c a) r a' 

newtype SubField v c a Source

Constructors

SubField ((String, DbType), [(String, EmbeddedDef)]) 

Instances

~ * r (HFalse, a) => ExtractValue (SubField v c a) r 
(PersistEntity v, Constructor c, Projection (SubField v c a) r a') => FieldLike (SubField v c a) r a' 
(PersistEntity v, Constructor c, PersistField a, ~ * v v', ~ ((* -> *) -> *) c c') => Expression (SubField v c a) v' c' 
(PersistEntity v, Constructor c, PersistField a) => Projection (SubField v c a) (RestrictionHolder v c) a 

data AutoKeyField v c whereSource

It can be used in expressions like a regular field. Note that the constructor should be specified for the condition. For example, delete (AutoKeyField asTypeOf (undefined :: f v SomeConstructor) ==. k) or delete (AutoKeyField ==. k ||. SomeField ==. "DUPLICATE")

Constructors

AutoKeyField :: (PersistEntity v, Constructor c) => AutoKeyField v c 

Instances

class NeverNull a Source

Types which when converted to PersistValue are never NULL. Consider the type Maybe (Maybe a). Now Nothing is stored as NULL, so we cannot distinguish between Just Nothing and Nothing which is a problem. The purpose of this class is to ban the inner Maybe's. Maybe this class can be removed when support for inner Maybe's appears.

class Numeric a Source

Constraint for use in arithmetic expressions. Num is not used to explicitly include only types supported by the library. TODO: consider replacement with Num

data Arith v c a Source

Arithmetic expressions which can include fields and literals

Constructors

Plus (Arith v c a) (Arith v c a) 
Minus (Arith v c a) (Arith v c a) 
Mult (Arith v c a) (Arith v c a) 
Abs (Arith v c a) 
forall f . FieldLike f (RestrictionHolder v c) a => ArithField f 
Lit Int64 

Instances

(PersistEntity v, Constructor c) => Eq (Arith v c a) 
(PersistEntity v, Constructor c, Numeric a) => Num (Arith v c a) 
(PersistEntity v, Constructor c) => Show (Arith v c a) 
~ * r (HFalse, a) => ExtractValue (Arith v c a) r 
(PersistEntity v, Constructor c, PersistField a, ~ * v v', ~ ((* -> *) -> *) c c') => Expression (Arith v c a) v' c' 

data Expr v c a whereSource

Used to uniformly represent fields, constants and arithmetic expressions. A value should be converted to Expr for usage in expressions

Constructors

ExprField :: (PersistEntity v, FieldLike f (RestrictionHolder v c) a') => f -> Expr v c f 
ExprArith :: PersistEntity v => Arith v c a -> Expr v c (Arith v c a) 
ExprPure :: forall v c a. PurePersistField a => a -> Expr v c a 

data Order v c Source

Defines sort order of a result-set

Constructors

forall a f . FieldLike f (RestrictionHolder v c) a => Asc f 
forall a f . FieldLike f (RestrictionHolder v c) a => Desc f 

class HasSelectOptions a v c | a -> v c whereSource

Associated Types

type HasLimit a Source

type HasOffset a Source

type HasOrder a Source

Instances

HasSelectOptions (Cond v c) v c 
HasSelectOptions (SelectOptions v c hasLimit hasOffset hasOrder) v c 

data SelectOptions v c hasLimit hasOffset hasOrder Source

Instances

HasSelectOptions (SelectOptions v c hasLimit hasOffset hasOrder) v c 

Type description

data DbType Source

A DB data type. Naming attempts to reflect the underlying Haskell datatypes, eg DbString instead of DbVarchar. Different databases may have different translations for these types.

Instances

data EntityDef Source

Describes an ADT.

Constructors

EntityDef 

Fields

entityName :: String

Entity name. entityName (entityDef v) == persistName v

typeParams :: [DbType]

Named types of the instantiated polymorphic type parameters

constructors :: [ConstructorDef]

List of entity constructors definitions

data EmbeddedDef Source

The first argument is a flag which defines if the field names should be concatenated with the outer field name (False) or used as is which provides full control over table column names (True). Value False should be the default value so that a datatype can be embedded without name conflict concern. The second argument list of field names and field types.

Constructors

EmbeddedDef Bool [(String, DbType)] 

data ConstructorDef Source

Describes an entity constructor

Constructors

ConstructorDef 

Fields

constrNum :: Int

Number of the constructor in the ADT

constrName :: String

Constructor name

constrAutoKeyName :: Maybe String

Autokey name if any

constrParams :: [(String, DbType)]

Parameter names with their named type

constrUniques :: [UniqueDef]

Uniqueness constraints on the constructor fiels

class Constructor c whereSource

Phantom constructors are made instances of this class. This class should be used only by Template Haskell codegen

Methods

phantomConstrName :: c (a :: * -> *) -> StringSource

phantomConstrNum :: c (a :: * -> *) -> IntSource

class (Constructor (UniqueConstr uKey), PurePersistField uKey) => IsUniqueKey uKey whereSource

Associated Types

type UniqueConstr uKey :: (* -> *) -> *Source

Methods

extractUnique :: uKey ~ Key v u => v -> uKeySource

uniqueNum :: uKey -> IntSource

data UniqueDef Source

Unique name and list of the field names that form a unique combination. Only fields of PrimitivePersistField types can be used in a unique definition

Constructors

UniqueDef 

Migration

type SingleMigration = Either [String] [(Bool, Int, String)]Source

Either error messages or migration queries with safety flag and execution order

type NamedMigrations = Map String SingleMigrationSource

Datatype names and corresponding migrations

Database

class (Monad m, DbDescriptor (PhantomDb m)) => PersistBackend m whereSource

Associated Types

type PhantomDb m Source

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

Methods

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

Insert a new record to a database and return its Key

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.

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

Return a list of the records satisfying the condition

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

Return a list of all records. Order is undefined. It is 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, Constructor c) => [Update v c] -> Cond v c -> m ()Source

Update the records satisfying the condition

delete :: (PersistEntity v, Constructor c) => Cond v c -> m ()Source

Remove the records satisfying the condition

deleteByKey :: (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

count :: (PersistEntity v, Constructor c) => Cond v c -> m IntSource

Count total number of records satisfying the condition

countAll :: PersistEntity v => v -> m IntSource

Count total number of records with all constructors

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

Fetch projection of some fields

migrate :: PersistEntity v => v -> Migration mSource

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

executeRawSource

Arguments

:: Bool

keep in cache

-> String

query

-> [PersistValue]

positional parameters

-> m () 

Execute raw query

queryRawSource

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 Int64Source

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

class PrimitivePersistField (AutoKeyType a) => DbDescriptor a Source

Associated Types

type AutoKeyType a Source

Type of the database default autoincremented key. For example, Sqlite has Int64

newtype Monad m => DbPersist conn m a Source

Constructors

DbPersist 

Fields

unDbPersist :: ReaderT conn m a
 

Instances

runDbPersist :: Monad m => DbPersist conn m a -> conn -> m aSource