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

Safe HaskellNone

Database.Groundhog.Expression

Description

This module provides mechanism for flexible and typesafe usage of plain data values and fields. The expressions can used in conditions and right part of Update statement. Example:

 StringField ==. "abc" &&. NumberField >. (0 :: Int) ||. MaybeField ==. (Nothing :: Maybe String) ||. MaybeField ==. Just "def"

Note that polymorphic values like numbers or Nothing must have a type annotation. Comparison operators specific for SQL such as IN and LIKE are defined in Database.Groundhog.Generic.Sql.Functions.

Synopsis

Documentation

class Expression db r a whereSource

Instances of this type can be converted to UntypedExpr. It is useful for uniform manipulation over fields, constant values, etc.

Methods

toExpr :: a -> UntypedExpr db rSource

Instances

PurePersistField a => Expression db r a 
(PersistEntity v, IsUniqueKey k, ~ * k (Key v (Unique u)), ~ * (RestrictionHolder v c) r') => Expression db r' (u (UniqueMarker v)) 
(~ * db' db, ~ * r' r) => Expression db' r' (Cond db r) 
(EntityConstr v c, ~ * (RestrictionHolder v c) r') => Expression db r' (AutoKeyField v c) 
(EntityConstr v c, PersistField a, ~ * (RestrictionHolder v c) r') => Expression db r' (SubField v c a) 
(EntityConstr v c, PersistField a, ~ * (RestrictionHolder v c) r') => Expression db r' (Field v c a) 
(PersistField a, ~ * db' db, ~ * r' r) => Expression db' r' (Expr db r a) 

class Unifiable a b Source

Instances

(Normalize bk a (ak, r), Normalize ak b (bk, r)) => Unifiable a b 
Unifiable a a 

class (Expression db r a, PersistField a') => ExpressionOf db r a a' Source

This helper class can make type signatures more concise

Instances

(Expression db r a, Normalize HTrue a (flag, a'), PersistField a') => ExpressionOf db r a a' 

(=.) :: (FieldLike f db r a', Expression db r b, Unifiable f b) => f -> b -> Update db rSource

Update field

(&&.) :: Cond db r -> Cond db r -> Cond db rSource

Boolean "and" operator.

(||.) :: Cond db r -> Cond db r -> Cond db rSource

Boolean "or" operator.

(==.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db rSource

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

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

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

(>.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db rSource

(>=.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db rSource

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

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).

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.