Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
null expressions and handlers
Synopsis
- null_ :: Expr ('Null ty)
- just_ :: 'NotNull ty --> 'Null ty
- unsafeNotNull :: 'Null ty --> 'NotNull ty
- monoNotNull :: (forall null. Expression grp lat with db params from (null ty)) -> Expression grp lat with db params from ('NotNull ty)
- coalesce :: FunctionVar ('Null ty) (null ty) (null ty)
- fromNull :: Expression grp lat with db params from ('NotNull ty) -> Expression grp lat with db params from ('Null ty) -> Expression grp lat with db params from ('NotNull ty)
- isNull :: 'Null ty --> null 'PGbool
- isNotNull :: 'Null ty --> null 'PGbool
- matchNull :: Expression grp lat with db params from nullty -> (Expression grp lat with db params from ('NotNull ty) -> Expression grp lat with db params from nullty) -> Expression grp lat with db params from ('Null ty) -> Expression grp lat with db params from nullty
- nullIf :: '['NotNull ty, 'NotNull ty] ---> 'Null ty
- type family CombineNullity (lhs :: PGType -> NullType) (rhs :: PGType -> NullType) :: PGType -> NullType where ...
- notNull :: 'NotNull ty --> 'Null ty
Null
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.
:: (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)
:: Expression grp lat with db params from ('NotNull ty) | what to convert |
-> 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)
:: Expression grp lat with db params from nullty | what to convert |
-> (Expression grp lat with db params from ('NotNull ty) -> Expression grp lat with db params from nullty) | function to perform when |
-> 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
type family CombineNullity (lhs :: PGType -> NullType) (rhs :: PGType -> NullType) :: PGType -> NullType where ... Source #
CombineNullity 'NotNull 'NotNull = 'NotNull | |
CombineNullity _ _ = 'Null |