squeal-postgresql-0.5.2.0: Squeal PostgreSQL Library

Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Expression.Comparison

Description

Comparison functions and operators

Synopsis

Documentation

(.==) :: Operator (null0 ty) (null1 ty) (Null PGbool) infix 4 Source #

Comparison operations like .==, ./=, .>, .>=, .< and .<= will produce NULLs if one of their arguments is NULL.

>>> 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)

(.>) :: Operator (null0 ty) (null1 ty) (Null PGbool) infix 4 Source #

>>> printSQL $ true .> null_
(TRUE > NULL)

greatest :: FunctionVar ty ty ty Source #

>>> let expr = greatest [param @1] currentTimestamp :: Expression outer commons grp schemas '[ 'NotNull 'PGtimestamptz] from ('NotNull 'PGtimestamptz)
>>> printSQL expr
GREATEST(($1 :: timestamp with time zone), CURRENT_TIMESTAMP)

least :: FunctionVar ty ty ty Source #

>>> printSQL $ least [null_] currentTimestamp
LEAST(NULL, CURRENT_TIMESTAMP)

type BetweenExpr Source #

Arguments

 = Expression outer commons grp schemas params from ty 
-> (Expression outer commons grp schemas params from ty, Expression outer commons grp schemas params from ty)

bounds

-> Condition outer commons grp schemas 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

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) (NotNull 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)

isUnknown :: null0 PGbool :--> null1 PGbool Source #

is unknown

>>> printSQL $ true & isUnknown
(TRUE IS UNKNOWN)

isNotUnknown :: null0 PGbool :--> null1 PGbool Source #

is true or false

>>> printSQL $ true & isNotUnknown
(TRUE IS NOT UNKNOWN)