{-# LANGUAGE
DataKinds
, OverloadedStrings
, TypeOperators
#-}
module Squeal.PostgreSQL.Expression.Logic
(
Condition
, true
, false
, not_
, (.&&)
, (.||)
, caseWhenThenElse
, ifThenElse
) where
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
type Condition grp lat with db params from =
Expression grp lat with db params from ('Null 'PGbool)
true :: Expr (null 'PGbool)
true :: Expression grp lat with db params from (null 'PGbool)
true = ByteString -> Expression grp lat with db params from (null 'PGbool)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"TRUE"
false :: Expr (null 'PGbool)
false :: Expression grp lat with db params from (null 'PGbool)
false = ByteString -> Expression grp lat with db params from (null 'PGbool)
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"FALSE"
not_ :: null 'PGbool --> null 'PGbool
not_ :: Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool)
not_ = ByteString -> null 'PGbool --> null 'PGbool
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeLeftOp ByteString
"NOT"
(.&&) :: Operator (null 'PGbool) (null 'PGbool) (null 'PGbool)
infixr 3 .&&
.&& :: Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool)
(.&&) = ByteString -> Operator (null 'PGbool) (null 'PGbool) (null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"AND"
(.||) :: Operator (null 'PGbool) (null 'PGbool) (null 'PGbool)
infixr 2 .||
.|| :: Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool)
(.||) = ByteString -> Operator (null 'PGbool) (null 'PGbool) (null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"OR"
caseWhenThenElse
:: [ ( Condition grp lat with db params from
, Expression grp lat with db params from ty
) ]
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
caseWhenThenElse :: [(Condition grp lat with db params from,
Expression grp lat with db params from ty)]
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
caseWhenThenElse [(Condition grp lat with db params from,
Expression grp lat with db params from ty)]
whenThens Expression grp lat with db params from ty
else_ = ByteString -> Expression grp lat with db params from ty
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression grp lat with db params from ty)
-> ByteString -> Expression grp lat with db params from ty
forall a b. (a -> b) -> a -> b
$ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
[ ByteString
"CASE"
, [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
[ [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat
[ ByteString
" WHEN ", Condition grp lat with db params from -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Condition grp lat with db params from
when_
, ByteString
" THEN ", Expression grp lat with db params from ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ty
then_
]
| (Condition grp lat with db params from
when_,Expression grp lat with db params from ty
then_) <- [(Condition grp lat with db params from,
Expression grp lat with db params from ty)]
whenThens
]
, ByteString
" ELSE ", Expression grp lat with db params from ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression grp lat with db params from ty
else_
, ByteString
" END"
]
ifThenElse
:: Condition grp lat with db params from
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
ifThenElse :: Condition grp lat with db params from
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
ifThenElse Condition grp lat with db params from
if_ Expression grp lat with db params from ty
then_ Expression grp lat with db params from ty
else_ = [(Condition grp lat with db params from,
Expression grp lat with db params from ty)]
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
forall (grp :: Grouping) (lat :: FromType) (with :: FromType)
(db :: SchemasType) (params :: [NullType]) (from :: FromType)
(ty :: NullType).
[(Condition grp lat with db params from,
Expression grp lat with db params from ty)]
-> Expression grp lat with db params from ty
-> Expression grp lat with db params from ty
caseWhenThenElse [(Condition grp lat with db params from
if_,Expression grp lat with db params from ty
then_)] Expression grp lat with db params from ty
else_