{-# 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.Schema
type Condition outer commons grp schemas params from =
Expression outer commons grp schemas params from ('Null 'PGbool)
true :: Expr (null 'PGbool)
true = UnsafeExpression "TRUE"
false :: Expr (null 'PGbool)
false = UnsafeExpression "FALSE"
not_ :: null 'PGbool :--> null 'PGbool
not_ = unsafeUnaryOpL "NOT"
(.&&) :: Operator (null 'PGbool) (null 'PGbool) (null 'PGbool)
infixr 3 .&&
(.&&) = unsafeBinaryOp "AND"
(.||) :: Operator (null 'PGbool) (null 'PGbool) (null 'PGbool)
infixr 2 .||
(.||) = unsafeBinaryOp "OR"
caseWhenThenElse
:: [ ( Condition outer commons grp schemas params from
, Expression outer commons grp schemas params from ty
) ]
-> Expression outer commons grp schemas params from ty
-> Expression outer commons grp schemas params from ty
caseWhenThenElse whenThens else_ = UnsafeExpression $ mconcat
[ "CASE"
, mconcat
[ mconcat
[ " WHEN ", renderSQL when_
, " THEN ", renderSQL then_
]
| (when_,then_) <- whenThens
]
, " ELSE ", renderSQL else_
, " END"
]
ifThenElse
:: Condition outer commons grp schemas params from
-> Expression outer commons grp schemas params from ty
-> Expression outer commons grp schemas params from ty
-> Expression outer commons grp schemas params from ty
ifThenElse if_ then_ else_ = caseWhenThenElse [(if_,then_)] else_