{-# LANGUAGE
OverloadedStrings
, RankNTypes
, TypeInType
, TypeOperators
#-}
module Squeal.PostgreSQL.Expression.Comparison
( (.==)
, (./=)
, (.>=)
, (.<)
, (.<=)
, (.>)
, greatest
, least
, BetweenExpr
, between
, notBetween
, betweenSymmetric
, notBetweenSymmetric
, isDistinctFrom
, isNotDistinctFrom
, isTrue
, isNotTrue
, isFalse
, isNotFalse
, isUnknown
, isNotUnknown
) where
import Data.ByteString
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.Logic
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Schema
(.==) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(.==) = unsafeBinaryOp "="
infix 4 .==
(./=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(./=) = unsafeBinaryOp "<>"
infix 4 ./=
(.>=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(.>=) = unsafeBinaryOp ">="
infix 4 .>=
(.<) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(.<) = unsafeBinaryOp "<"
infix 4 .<
(.<=) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(.<=) = unsafeBinaryOp "<="
infix 4 .<=
(.>) :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
(.>) = unsafeBinaryOp ">"
infix 4 .>
greatest :: FunctionVar ty ty ty
greatest = unsafeFunctionVar "GREATEST"
least :: FunctionVar ty ty ty
least = unsafeFunctionVar "LEAST"
type BetweenExpr
= forall outer commons grp schemas params from ty
. Expression outer commons grp schemas params from ty
-> ( Expression outer commons grp schemas params from ty
, Expression outer commons grp schemas params from ty )
-> Condition outer commons grp schemas params from
unsafeBetweenExpr :: ByteString -> BetweenExpr
unsafeBetweenExpr fun a (x,y) = UnsafeExpression $
renderSQL a <+> fun <+> renderSQL x <+> "AND" <+> renderSQL y
between :: BetweenExpr
between = unsafeBetweenExpr "BETWEEN"
notBetween :: BetweenExpr
notBetween = unsafeBetweenExpr "NOT BETWEEN"
betweenSymmetric :: BetweenExpr
betweenSymmetric = unsafeBetweenExpr "BETWEEN SYMMETRIC"
notBetweenSymmetric :: BetweenExpr
notBetweenSymmetric = unsafeBetweenExpr "NOT BETWEEN SYMMETRIC"
isDistinctFrom :: Operator (null0 ty) (null1 ty) ('Null 'PGbool)
isDistinctFrom = unsafeBinaryOp "IS DISTINCT FROM"
isNotDistinctFrom :: Operator (null0 ty) (null1 ty) ('NotNull 'PGbool)
isNotDistinctFrom = unsafeBinaryOp "IS NOT DISTINCT FROM"
isTrue :: null0 'PGbool :--> null1 'PGbool
isTrue = unsafeUnaryOpR "IS TRUE"
isNotTrue :: null0 'PGbool :--> null1 'PGbool
isNotTrue = unsafeUnaryOpR "IS NOT TRUE"
isFalse :: null0 'PGbool :--> null1 'PGbool
isFalse = unsafeUnaryOpR "IS FALSE"
isNotFalse :: null0 'PGbool :--> null1 'PGbool
isNotFalse = unsafeUnaryOpR "IS NOT FALSE"
isUnknown :: null0 'PGbool :--> null1 'PGbool
isUnknown = unsafeUnaryOpR "IS UNKNOWN"
isNotUnknown :: null0 'PGbool :--> null1 'PGbool
isNotUnknown = unsafeUnaryOpR "IS NOT UNKNOWN"