Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
comparison functions and operators
Synopsis
- (.==) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
- (./=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
- (.>=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
- (.<) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
- (.<=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
- (.>) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
- greatest :: FunctionVar ty ty ty
- least :: FunctionVar ty ty ty
- type BetweenExpr = forall grp lat with db params from ty. Expression grp lat with db params from ty -> (Expression grp lat with db params from ty, Expression grp lat with db params from ty) -> Condition grp lat with db params from
- between :: BetweenExpr
- notBetween :: BetweenExpr
- betweenSymmetric :: BetweenExpr
- notBetweenSymmetric :: BetweenExpr
- isDistinctFrom :: Operator (null0 ty) (null1 ty) (null 'PGbool)
- isNotDistinctFrom :: Operator (null0 ty) (null1 ty) (null 'PGbool)
- isTrue :: null0 'PGbool --> null1 'PGbool
- isNotTrue :: null0 'PGbool --> null1 'PGbool
- isFalse :: null0 'PGbool --> null1 'PGbool
- isNotFalse :: null0 'PGbool --> null1 'PGbool
- isUnknown :: null0 'PGbool --> null1 'PGbool
- isNotUnknown :: null0 'PGbool --> null1 'PGbool
Comparison Operators
(./=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool) infix 4 Source #
>>>
printSQL $ true ./= null_
(TRUE <> NULL)
(.>=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool) infix 4 Source #
>>>
printSQL $ true .>= null_
(TRUE >= NULL)
(.<) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool) infix 4 Source #
>>>
printSQL $ true .< null_
(TRUE < NULL)
(.<=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool) infix 4 Source #
>>>
printSQL $ true .<= null_
(TRUE <= NULL)
(.>) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool) infix 4 Source #
>>>
printSQL $ true .> null_
(TRUE > NULL)
Comparison Functions
greatest :: FunctionVar ty ty ty Source #
>>>
let expr = greatest [param @1] currentTimestamp
>>>
printSQL expr
GREATEST(($1 :: timestamp with time zone), CURRENT_TIMESTAMP)
least :: FunctionVar ty ty ty Source #
>>>
printSQL $ least [null_] currentTimestamp
LEAST(NULL, CURRENT_TIMESTAMP)
Between
type BetweenExpr Source #
= forall grp lat with db params from ty. Expression grp lat with db params from ty | |
-> (Expression grp lat with db params from ty, Expression grp lat with db params from ty) | bounds |
-> Condition grp lat with db params from |
A RankNType
for comparison expressions like between
.
between :: BetweenExpr Source #
>>>
printSQL $ true `between` (null_, false)
TRUE BETWEEN NULL AND FALSE
notBetween :: BetweenExpr Source #
>>>
printSQL $ true `notBetween` (null_, false)
TRUE NOT BETWEEN NULL AND FALSE
betweenSymmetric :: BetweenExpr Source #
between, after sorting the comparison values
>>>
printSQL $ true `betweenSymmetric` (null_, false)
TRUE BETWEEN SYMMETRIC NULL AND FALSE
notBetweenSymmetric :: BetweenExpr Source #
not between, after sorting the comparison values
>>>
printSQL $ true `notBetweenSymmetric` (null_, false)
TRUE NOT BETWEEN SYMMETRIC NULL AND FALSE
Null Comparison
isDistinctFrom :: Operator (null0 ty) (null1 ty) (null 'PGbool) Source #
not equal, treating null like an ordinary value
>>>
printSQL $ true `isDistinctFrom` null_
(TRUE IS DISTINCT FROM NULL)
isNotDistinctFrom :: Operator (null0 ty) (null1 ty) (null 'PGbool) Source #
equal, treating null like an ordinary value
>>>
printSQL $ true `isNotDistinctFrom` null_
(TRUE IS NOT DISTINCT FROM NULL)
isTrue :: null0 'PGbool --> null1 'PGbool Source #
is true
>>>
printSQL $ true & isTrue
(TRUE IS TRUE)
isNotTrue :: null0 'PGbool --> null1 'PGbool Source #
is false or unknown
>>>
printSQL $ true & isNotTrue
(TRUE IS NOT TRUE)
isFalse :: null0 'PGbool --> null1 'PGbool Source #
is false
>>>
printSQL $ true & isFalse
(TRUE IS FALSE)
isNotFalse :: null0 'PGbool --> null1 'PGbool Source #
is true or unknown
>>>
printSQL $ true & isNotFalse
(TRUE IS NOT FALSE)