{-# LANGUAGE
DataKinds
, OverloadedStrings
, TypeOperators
#-}
module Squeal.PostgreSQL.Expression.Null
( null_
, notNull
, coalesce
, fromNull
, isNull
, isNotNull
, matchNull
, nullIf
) where
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.Logic
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Schema
null_ :: Expr ('Null ty)
null_ = UnsafeExpression "NULL"
notNull :: 'NotNull ty :--> 'Null ty
notNull = UnsafeExpression . renderSQL
coalesce :: FunctionVar ('Null ty) ('NotNull ty) ('NotNull ty)
coalesce nullxs notNullx = UnsafeExpression $
"COALESCE" <> parenthesized (commaSeparated
((renderSQL <$> nullxs) <> [renderSQL notNullx]))
fromNull
:: Expression outer commons grp schemas params from ('NotNull ty)
-> Expression outer commons grp schemas params from ('Null ty)
-> Expression outer commons grp schemas params from ('NotNull ty)
fromNull notNullx nullx = coalesce [nullx] notNullx
isNull :: 'Null ty :--> null 'PGbool
isNull x = UnsafeExpression $ renderSQL x <+> "IS NULL"
isNotNull :: 'Null ty :--> null 'PGbool
isNotNull x = UnsafeExpression $ renderSQL x <+> "IS NOT NULL"
matchNull
:: Expression outer commons grp schemas params from (nullty)
-> ( Expression outer commons grp schemas params from ('NotNull ty)
-> Expression outer commons grp schemas params from (nullty) )
-> Expression outer commons grp schemas params from ('Null ty)
-> Expression outer commons grp schemas params from (nullty)
matchNull y f x = ifThenElse (isNull x) y
(f (UnsafeExpression (renderSQL x)))
nullIf :: FunctionN '[ 'NotNull ty, 'NotNull ty] ('Null ty)
nullIf = unsafeFunctionN "NULLIF"