Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- class Expression db r a where
- toExpr :: a -> UntypedExpr db r
- class Unifiable a b
- class (Expression db r a, PersistField a') => ExpressionOf db r a a' | a -> a'
- (=.) :: (Assignable f a', ProjectionDb f db, ProjectionRestriction f r, Expression db r b, Unifiable f b) => f -> b -> Update db r
- (&&.) :: Cond db r -> Cond db r -> Cond db r
- (||.) :: Cond db r -> Cond db r -> Cond db r
- (==.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r
- (/=.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r
- (<.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r
- (<=.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r
- (>.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r
- (>=.) :: (Expression db r a, Expression db r b, Unifiable a b) => a -> b -> Cond db r
- isFieldNothing :: (Expression db r f, Projection f (Maybe a), PrimitivePersistField (Maybe a), Unifiable f (Maybe a)) => f -> Cond db r
- liftExpr :: ExpressionOf db r a a' => a -> Expr db r a'
- toArith :: ExpressionOf db r a a' => a -> Expr db r a'
Documentation
class Expression db r a where Source #
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 r Source #
Instances
Instances
(Normalize bk a (ak, r), Normalize ak b (bk, r)) => Unifiable a b Source # | |
Defined in Database.Groundhog.Expression | |
Unifiable a a Source # | |
Defined in Database.Groundhog.Expression |
class (Expression db r a, PersistField a') => ExpressionOf db r a a' | 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' Source # | |
Defined in Database.Groundhog.Expression |
(=.) :: (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
(==.) :: (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".