squeal-postgresql-0.9.1.3: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Squeal.PostgreSQL.Expression.Null

Contents

Description

null expressions and handlers

Synopsis

Null

null_ :: Expr ('Null ty) Source #

analagous to Nothing

>>> printSQL null_
NULL

just_ :: 'NotNull ty --> 'Null ty Source #

analagous to Just

>>> printSQL $ just_ true
TRUE

unsafeNotNull :: 'Null ty --> 'NotNull ty Source #

Analagous to fromJust inverse to notNull, useful when you know an Expression is NotNull, because, for instance, you've filtered out NULL values in a column.

monoNotNull Source #

Arguments

:: (forall null. Expression grp lat with db params from (null ty))

null polymorphic

-> Expression grp lat with db params from ('NotNull ty) 

Some expressions are null polymorphic which may raise inference issues. Use monoNotNull to fix their nullity as NotNull.

coalesce :: FunctionVar ('Null ty) (null ty) (null ty) Source #

return the leftmost value which is not NULL

>>> printSQL $ coalesce [null_, true] false
COALESCE(NULL, TRUE, FALSE)

fromNull Source #

Arguments

:: Expression grp lat with db params from ('NotNull ty)

what to convert NULL to

-> Expression grp lat with db params from ('Null ty) 
-> Expression grp lat with db params from ('NotNull ty) 

analagous to fromMaybe using COALESCE

>>> printSQL $ fromNull true null_
COALESCE(NULL, TRUE)

isNull :: 'Null ty --> null 'PGbool Source #

>>> printSQL $ null_ & isNull
NULL IS NULL

isNotNull :: 'Null ty --> null 'PGbool Source #

>>> printSQL $ null_ & isNotNull
NULL IS NOT NULL

matchNull Source #

Arguments

:: Expression grp lat with db params from nullty

what to convert NULL to

-> (Expression grp lat with db params from ('NotNull ty) -> Expression grp lat with db params from nullty)

function to perform when NULL is absent

-> Expression grp lat with db params from ('Null ty) 
-> Expression grp lat with db params from nullty 

analagous to maybe using IS NULL

>>> printSQL $ matchNull true not_ null_
CASE WHEN NULL IS NULL THEN TRUE ELSE (NOT NULL) END

nullIf :: '['NotNull ty, 'NotNull ty] ---> 'Null ty Source #

right inverse to fromNull, if its arguments are equal then nullIf gives NULL.

>>> :set -XTypeApplications
>>> printSQL (nullIf (false *: param @1))
NULLIF(FALSE, ($1 :: bool))

type family CombineNullity (lhs :: PGType -> NullType) (rhs :: PGType -> NullType) :: PGType -> NullType where ... Source #

Make the return type of the type family NotNull if both arguments are, or Null otherwise.

notNull :: 'NotNull ty --> 'Null ty Source #

Deprecated: use just_ instead

analagous to Just