squeal-postgresql-0.4.0.0: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.Expression

Contents

Description

Squeal expressions are the atoms used to build statements.

Synopsis

Expression

newtype Expression (schema :: SchemaType) (from :: FromType) (grouping :: Grouping) (params :: [NullityType]) (ty :: NullityType) Source #

Expressions are used in a variety of contexts, such as in the target list of the select command, as new column values in insertRow or update, or in search Conditions in a number of commands.

The expression syntax allows the calculation of values from primitive expression using arithmetic, logical, and other operations.

Instances
(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (Aliased (Expression schema from (Grouped bys) params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> Aliased (Expression schema from (Grouped bys) params) (column ::: ty) Source #

(Has table from columns, Has column columns ty) => IsQualified table column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty) => IsQualified table column (Aliased (Expression schema from Ungrouped params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> Aliased (Expression schema from Ungrouped params) (column ::: ty) Source #

(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (Expression schema from (Grouped bys) params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> Expression schema from (Grouped bys) params ty Source #

(Has table from columns, Has column columns ty) => IsQualified table column (Expression schema from Ungrouped params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> Expression schema from Ungrouped params ty Source #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (Aliased (Expression schema from (Grouped bys) params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression schema from (Grouped bys) params) (column ::: ty) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (Aliased (Expression schema from Ungrouped params) (column ::: ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Aliased (Expression schema from Ungrouped params) (column ::: ty) #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (Expression schema from (Grouped bys) params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Expression schema from (Grouped bys) params ty #

(HasUnique table from columns, Has column columns ty) => IsLabel column (Expression schema from Ungrouped params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Expression schema from Ungrouped params ty #

(KnownSymbol label, In label labels) => IsPGlabel label (Expression schema from grouping params (nullity (PGenum labels))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

label :: Expression schema from grouping params (nullity (PGenum labels)) Source #

Eq (Expression schema from grouping params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(==) :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Bool #

(/=) :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Bool #

(In ty PGNum, In ty PGFloating) => Floating (Expression schema from grouping params (nullity ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pi :: Expression schema from grouping params (nullity ty) #

exp :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

log :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

sqrt :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

(**) :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

logBase :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

sin :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

cos :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

tan :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

asin :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

acos :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

atan :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

sinh :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

cosh :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

tanh :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

asinh :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

acosh :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

atanh :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

log1p :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

expm1 :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

log1pexp :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

log1mexp :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

(In ty PGNum, In ty PGFloating) => Fractional (Expression schema from grouping params (nullity ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(/) :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

recip :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

fromRational :: Rational -> Expression schema from grouping params (nullity ty) #

In ty PGNum => Num (Expression schema from grouping params (nullity ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(+) :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

(-) :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

(*) :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

negate :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

abs :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

signum :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity ty) #

fromInteger :: Integer -> Expression schema from grouping params (nullity ty) #

Ord (Expression schema from grouping params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

compare :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Ordering #

(<) :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Bool #

(<=) :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Bool #

(>) :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Bool #

(>=) :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Bool #

max :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Expression schema from grouping params ty #

min :: Expression schema from grouping params ty -> Expression schema from grouping params ty -> Expression schema from grouping params ty #

Show (Expression schema from grouping params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

showsPrec :: Int -> Expression schema from grouping params ty -> ShowS #

show :: Expression schema from grouping params ty -> String #

showList :: [Expression schema from grouping params ty] -> ShowS #

IsString (Expression schema from grouping params (nullity PGtext)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromString :: String -> Expression schema from grouping params (nullity PGtext) #

Generic (Expression schema from grouping params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Associated Types

type Rep (Expression schema from grouping params ty) :: * -> * #

Methods

from :: Expression schema from grouping params ty -> Rep (Expression schema from grouping params ty) x #

to :: Rep (Expression schema from grouping params ty) x -> Expression schema from grouping params ty #

Semigroup (Expression schema from grouping param (nullity PGjsonb)) Source #

Concatenate two jsonb values into a new jsonb value.

Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(<>) :: Expression schema from grouping param (nullity PGjsonb) -> Expression schema from grouping param (nullity PGjsonb) -> Expression schema from grouping param (nullity PGjsonb) #

sconcat :: NonEmpty (Expression schema from grouping param (nullity PGjsonb)) -> Expression schema from grouping param (nullity PGjsonb) #

stimes :: Integral b => b -> Expression schema from grouping param (nullity PGjsonb) -> Expression schema from grouping param (nullity PGjsonb) #

Semigroup (Expression schema from grouping params (nullity PGtext)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(<>) :: Expression schema from grouping params (nullity PGtext) -> Expression schema from grouping params (nullity PGtext) -> Expression schema from grouping params (nullity PGtext) #

sconcat :: NonEmpty (Expression schema from grouping params (nullity PGtext)) -> Expression schema from grouping params (nullity PGtext) #

stimes :: Integral b => b -> Expression schema from grouping params (nullity PGtext) -> Expression schema from grouping params (nullity PGtext) #

Semigroup (Expression schema from grouping params (nullity (PGvararray ty))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(<>) :: Expression schema from grouping params (nullity (PGvararray ty)) -> Expression schema from grouping params (nullity (PGvararray ty)) -> Expression schema from grouping params (nullity (PGvararray ty)) #

sconcat :: NonEmpty (Expression schema from grouping params (nullity (PGvararray ty))) -> Expression schema from grouping params (nullity (PGvararray ty)) #

stimes :: Integral b => b -> Expression schema from grouping params (nullity (PGvararray ty)) -> Expression schema from grouping params (nullity (PGvararray ty)) #

Monoid (Expression schema from grouping params (nullity PGtext)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

mempty :: Expression schema from grouping params (nullity PGtext) #

mappend :: Expression schema from grouping params (nullity PGtext) -> Expression schema from grouping params (nullity PGtext) -> Expression schema from grouping params (nullity PGtext) #

mconcat :: [Expression schema from grouping params (nullity PGtext)] -> Expression schema from grouping params (nullity PGtext) #

Monoid (Expression schema from grouping params (nullity (PGvararray ty))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

mempty :: Expression schema from grouping params (nullity (PGvararray ty)) #

mappend :: Expression schema from grouping params (nullity (PGvararray ty)) -> Expression schema from grouping params (nullity (PGvararray ty)) -> Expression schema from grouping params (nullity (PGvararray ty)) #

mconcat :: [Expression schema from grouping params (nullity (PGvararray ty))] -> Expression schema from grouping params (nullity (PGvararray ty)) #

NFData (Expression schema from grouping params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

rnf :: Expression schema from grouping params ty -> () #

RenderSQL (Expression schema from grouping params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

renderSQL :: Expression schema from grouping params ty -> ByteString Source #

type Rep (Expression schema from grouping params ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

type Rep (Expression schema from grouping params ty) = D1 (MetaData "Expression" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "UnsafeExpression" PrefixI True) (S1 (MetaSel (Just "renderExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

class KnownNat n => HasParameter (n :: Nat) (schema :: SchemaType) (params :: [NullityType]) (ty :: NullityType) | n params -> ty where Source #

A HasParameter constraint is used to indicate a value that is supplied externally to a SQL statement. manipulateParams, queryParams and traversePrepared support specifying data values separately from the SQL command string, in which case params are used to refer to the out-of-line data values.

Methods

parameter :: TypeExpression schema ty -> Expression schema from grouping params ty Source #

parameter takes a Nat using type application and a TypeExpression.

>>> let expr = parameter @1 int4 :: Expression sch rels grp '[ 'Null 'PGint4] ('Null 'PGint4)
>>> printSQL expr
($1 :: int4)
Instances
(KnownNat n, HasParameter (n - 1) schema params ty) => HasParameter n schema (ty' ': params) ty Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

parameter :: TypeExpression schema ty -> Expression schema from grouping (ty' ': params) ty Source #

HasParameter 1 schema (ty1 ': tys) ty1 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

parameter :: TypeExpression schema ty1 -> Expression schema from grouping (ty1 ': tys) ty1 Source #

param Source #

Arguments

:: (PGTyped schema ty, HasParameter n schema params ty) 
=> Expression schema from grouping params ty

param

param takes a Nat using type application and for basic types, infers a TypeExpression.

>>> let expr = param @1 :: Expression sch rels grp '[ 'Null 'PGint4] ('Null 'PGint4)
>>> printSQL expr
($1 :: int4)

Null

null_ :: Expression schema rels grouping params (Null ty) Source #

analagous to Nothing

>>> printSQL null_
NULL

notNull :: Expression schema rels grouping params (NotNull ty) -> Expression schema rels grouping params (Null ty) Source #

analagous to Just

>>> printSQL $ notNull true
TRUE

coalesce Source #

Arguments

:: [Expression schema from grouping params (Null ty)]

NULLs may be present

-> Expression schema from grouping params (NotNull ty)

NULL is absent

-> Expression schema from grouping params (NotNull ty) 

return the leftmost value which is not NULL

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

fromNull Source #

Arguments

:: Expression schema from grouping params (NotNull ty)

what to convert NULL to

-> Expression schema from grouping params (Null ty) 
-> Expression schema from grouping params (NotNull ty) 

analagous to fromMaybe using COALESCE

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

isNull Source #

Arguments

:: Expression schema from grouping params (Null ty)

possibly NULL

-> Condition schema from grouping params 
>>> printSQL $ null_ & isNull
NULL IS NULL

isNotNull Source #

Arguments

:: Expression schema from grouping params (Null ty)

possibly NULL

-> Condition schema from grouping params 
>>> printSQL $ null_ & isNotNull
NULL IS NOT NULL

matchNull Source #

Arguments

:: Expression schema from grouping params nullty

what to convert NULL to

-> (Expression schema from grouping params (NotNull ty) -> Expression schema from grouping params nullty)

function to perform when NULL is absent

-> Expression schema from grouping params (Null ty) 
-> Expression schema from grouping params nullty 

analagous to maybe using IS NULL

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

nullIf Source #

Arguments

:: Expression schema from grouping params (NotNull ty)

NULL is absent

-> Expression schema from grouping params (NotNull ty)

NULL is absent

-> Expression schema from grouping params (Null ty) 

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

>>> :set -XTypeApplications -XDataKinds
>>> let expr = nullIf false (param @1) :: Expression schema rels grp '[ 'NotNull 'PGbool] ('Null 'PGbool)
>>> printSQL expr
NULL IF (FALSE, ($1 :: bool))

Collections

array Source #

Arguments

:: [Expression schema from grouping params ty]

array elements

-> Expression schema from grouping params (nullity (PGvararray ty)) 
>>> printSQL $ array [null_, false, true]
ARRAY[NULL, FALSE, TRUE]

index Source #

Arguments

:: Word64

index

-> Expression schema from grouping params (nullity (PGvararray ty))

array

-> Expression schema from grouping params (NullifyType ty) 
>>> printSQL $ array [null_, false, true] & index 2
(ARRAY[NULL, FALSE, TRUE])[2]

row Source #

Arguments

:: SListI row 
=> NP (Aliased (Expression schema from grouping params)) row

zero or more expressions for the row field values

-> Expression schema from grouping params (nullity (PGcomposite row)) 

A row constructor is an expression that builds a row value (also called a composite value) using values for its member fields.

>>> :{
type Complex = 'PGcomposite
  '[ "real"      ::: 'NotNull 'PGfloat8
   , "imaginary" ::: 'NotNull 'PGfloat8 ]
:}
>>> let i = row (0 `as` #real :* 1 `as` #imaginary) :: Expression '[] '[] 'Ungrouped '[] ('NotNull Complex)
>>> printSQL i
ROW(0, 1)

field Source #

Arguments

:: (Has tydef schema (Typedef (PGcomposite row)), Has field row ty) 
=> Alias tydef

row type

-> Alias field

field name

-> Expression schema from grouping params (NotNull (PGcomposite row)) 
-> Expression schema from grouping params ty 
>>> :{
type Complex = 'PGcomposite
  '[ "real"      ::: 'NotNull 'PGfloat8
   , "imaginary" ::: 'NotNull 'PGfloat8 ]
:}
>>> let i = row (0 `as` #real :* 1 `as` #imaginary) :: Expression '["complex" ::: 'Typedef Complex] '[] 'Ungrouped '[] ('NotNull Complex)
>>> printSQL $ i & field #complex #imaginary
(ROW(0, 1)::"complex")."imaginary"

Functions

unsafeBinaryOp Source #

Arguments

:: ByteString

operator

-> Expression schema from grouping params ty0 
-> Expression schema from grouping params ty1 
-> Expression schema from grouping params ty2 
>>> printSQL $ unsafeBinaryOp "OR" true false
(TRUE OR FALSE)

unsafeUnaryOp Source #

Arguments

:: ByteString

operator

-> Expression schema from grouping params ty0 
-> Expression schema from grouping params ty1 
>>> printSQL $ unsafeUnaryOp "NOT" true
(NOT TRUE)

unsafeFunction Source #

Arguments

:: ByteString

function

-> Expression schema from grouping params xty 
-> Expression schema from grouping params yty 
>>> printSQL $ unsafeFunction "f" true
f(TRUE)

unsafeVariadicFunction Source #

Arguments

:: SListI elems 
=> ByteString

function

-> NP (Expression schema from grouping params) elems 
-> Expression schema from grouping params ret 

Helper for defining variadic functions.

atan2_ Source #

Arguments

:: float `In` PGFloating 
=> Expression schema from grouping params (nullity float)

numerator

-> Expression schema from grouping params (nullity float)

denominator

-> Expression schema from grouping params (nullity float) 
>>> :{
let
  expression :: Expression schema from grouping params (nullity 'PGfloat4)
  expression = atan2_ pi 2
in printSQL expression
:}
atan2(pi(), 2)

cast Source #

Arguments

:: TypeExpression schema ty1

type to cast as

-> Expression schema from grouping params ty0

value to convert

-> Expression schema from grouping params ty1 
>>> printSQL $ true & cast int4
(TRUE :: int4)

quot_ Source #

Arguments

:: int `In` PGIntegral 
=> Expression schema from grouping params (nullity int)

numerator

-> Expression schema from grouping params (nullity int)

denominator

-> Expression schema from grouping params (nullity int) 

integer division, truncates the result

>>> :{
let
  expression :: Expression schema from grouping params (nullity 'PGint2)
  expression = 5 `quot_` 2
in printSQL expression
:}
(5 / 2)

rem_ Source #

Arguments

:: int `In` PGIntegral 
=> Expression schema from grouping params (nullity int)

numerator

-> Expression schema from grouping params (nullity int)

denominator

-> Expression schema from grouping params (nullity int) 

remainder upon integer division

>>> :{
let
  expression :: Expression schema from grouping params (nullity 'PGint2)
  expression = 5 `rem_` 2
in printSQL expression
:}
(5 % 2)

trunc Source #

Arguments

:: frac `In` PGFloating 
=> Expression schema from grouping params (nullity frac)

fractional number

-> Expression schema from grouping params (nullity frac) 
>>> :{
let
  expression :: Expression schema from grouping params (nullity 'PGfloat4)
  expression = trunc pi
in printSQL expression
:}
trunc(pi())

round_ Source #

Arguments

:: frac `In` PGFloating 
=> Expression schema from grouping params (nullity frac)

fractional number

-> Expression schema from grouping params (nullity frac) 
>>> :{
let
  expression :: Expression schema from grouping params (nullity 'PGfloat4)
  expression = round_ pi
in printSQL expression
:}
round(pi())

ceiling_ Source #

Arguments

:: frac `In` PGFloating 
=> Expression schema from grouping params (nullity frac)

fractional number

-> Expression schema from grouping params (nullity frac) 
>>> :{
let
  expression :: Expression schema from grouping params (nullity 'PGfloat4)
  expression = ceiling_ pi
in printSQL expression
:}
ceiling(pi())

greatest Source #

Arguments

:: Expression schema from grouping params nullty

needs at least 1 argument

-> [Expression schema from grouping params nullty]

or more

-> Expression schema from grouping params nullty 
>>> let expr = greatest currentTimestamp [param @1] :: Expression sch rels grp '[ 'NotNull 'PGtimestamptz] ('NotNull 'PGtimestamptz)
>>> printSQL expr
GREATEST(CURRENT_TIMESTAMP, ($1 :: timestamp with time zone))

least Source #

Arguments

:: Expression schema from grouping params nullty

needs at least 1 argument

-> [Expression schema from grouping params nullty]

or more

-> Expression schema from grouping params nullty 
>>> printSQL $ least currentTimestamp [null_]
LEAST(CURRENT_TIMESTAMP, NULL)

Conditions

true :: Expression schema from grouping params (nullity PGbool) Source #

>>> printSQL true
TRUE

false :: Expression schema from grouping params (nullity PGbool) Source #

>>> printSQL false
FALSE

not_ :: Expression schema from grouping params (nullity PGbool) -> Expression schema from grouping params (nullity PGbool) Source #

>>> printSQL $ not_ true
(NOT TRUE)

(.&&) :: Expression schema from grouping params (nullity PGbool) -> Expression schema from grouping params (nullity PGbool) -> Expression schema from grouping params (nullity PGbool) infixr 3 Source #

>>> printSQL $ true .&& false
(TRUE AND FALSE)

(.||) :: Expression schema from grouping params (nullity PGbool) -> Expression schema from grouping params (nullity PGbool) -> Expression schema from grouping params (nullity PGbool) infixr 2 Source #

>>> printSQL $ true .|| false
(TRUE OR FALSE)

type Condition schema from grouping params = Expression schema from grouping params (Null PGbool) Source #

A Condition is an Expression, which can evaluate to true, false or null_. This is because SQL uses a three valued logic.

caseWhenThenElse Source #

Arguments

:: [(Condition schema from grouping params, Expression schema from grouping params ty)]

whens and thens

-> Expression schema from grouping params ty

else

-> Expression schema from grouping params ty 
>>> :{
let
  expression :: Expression schema from grouping params (nullity 'PGint2)
  expression = caseWhenThenElse [(true, 1), (false, 2)] 3
in printSQL expression
:}
CASE WHEN TRUE THEN 1 WHEN FALSE THEN 2 ELSE 3 END

ifThenElse Source #

Arguments

:: Condition schema from grouping params 
-> Expression schema from grouping params ty

then

-> Expression schema from grouping params ty

else

-> Expression schema from grouping params ty 
>>> :{
let
  expression :: Expression schema from grouping params (nullity 'PGint2)
  expression = ifThenElse true 1 0
in printSQL expression
:}
CASE WHEN TRUE THEN 1 ELSE 0 END

(.==) infix 4 Source #

Arguments

:: Expression schema from grouping params (nullity0 ty)

lhs

-> Expression schema from grouping params (nullity1 ty)

rhs

-> Condition schema from grouping params 

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

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

(./=) infix 4 Source #

Arguments

:: Expression schema from grouping params (nullity0 ty)

lhs

-> Expression schema from grouping params (nullity1 ty)

rhs

-> Condition schema from grouping params 
>>> printSQL $ true ./= null_
(TRUE <> NULL)

(.>=) infix 4 Source #

Arguments

:: Expression schema from grouping params (nullity0 ty)

lhs

-> Expression schema from grouping params (nullity1 ty)

rhs

-> Condition schema from grouping params 
>>> printSQL $ true .>= null_
(TRUE >= NULL)

(.<) infix 4 Source #

Arguments

:: Expression schema from grouping params (nullity0 ty)

lhs

-> Expression schema from grouping params (nullity1 ty)

rhs

-> Condition schema from grouping params 
>>> printSQL $ true .< null_
(TRUE < NULL)

(.<=) infix 4 Source #

Arguments

:: Expression schema from grouping params (nullity0 ty)

lhs

-> Expression schema from grouping params (nullity1 ty)

rhs

-> Condition schema from grouping params 
>>> printSQL $ true .<= null_
(TRUE <= NULL)

(.>) infix 4 Source #

Arguments

:: Expression schema from grouping params (nullity0 ty)

lhs

-> Expression schema from grouping params (nullity1 ty)

rhs

-> Condition schema from grouping params 
>>> printSQL $ true .> null_
(TRUE > NULL)

Time

currentDate :: Expression schema from grouping params (nullity PGdate) Source #

>>> printSQL currentDate
CURRENT_DATE

currentTime :: Expression schema from grouping params (nullity PGtimetz) Source #

>>> printSQL currentTime
CURRENT_TIME

currentTimestamp :: Expression schema from grouping params (nullity PGtimestamptz) Source #

>>> printSQL currentTimestamp
CURRENT_TIMESTAMP

localTime :: Expression schema from grouping params (nullity PGtime) Source #

>>> printSQL localTime
LOCALTIME

localTimestamp :: Expression schema from grouping params (nullity PGtimestamp) Source #

>>> printSQL localTimestamp
LOCALTIMESTAMP

Text

lower Source #

Arguments

:: Expression schema from grouping params (nullity PGtext)

string to lower case

-> Expression schema from grouping params (nullity PGtext) 
>>> printSQL $ lower "ARRRGGG"
lower(E'ARRRGGG')

upper Source #

Arguments

:: Expression schema from grouping params (nullity PGtext)

string to upper case

-> Expression schema from grouping params (nullity PGtext) 
>>> printSQL $ upper "eeee"
upper(E'eeee')

charLength Source #

Arguments

:: Expression schema from grouping params (nullity PGtext)

string to measure

-> Expression schema from grouping params (nullity PGint4) 
>>> printSQL $ charLength "four"
char_length(E'four')

like Source #

Arguments

:: Expression schema from grouping params (nullity PGtext)

string

-> Expression schema from grouping params (nullity PGtext)

pattern

-> Expression schema from grouping params (nullity PGbool) 

The like expression returns true if the string matches the supplied pattern. If pattern does not contain percent signs or underscores, then the pattern only represents the string itself; in that case like acts like the equals operator. An underscore (_) in pattern stands for (matches) any single character; a percent sign (%) matches any sequence of zero or more characters.

>>> printSQL $ "abc" `like` "a%"
(E'abc' LIKE E'a%')

Json

Json and Jsonb operators

(.->) :: (json `In` PGJsonType, key `In` PGJsonKey) => Expression schema from grouping params (nullity json) -> Expression schema from grouping params (nullity key) -> Expression schema from grouping params (Null json) infixl 8 Source #

Get JSON value (object field or array element) at a key.

(.->>) :: (json `In` PGJsonType, key `In` PGJsonKey) => Expression schema from grouping params (nullity json) -> Expression schema from grouping params (nullity key) -> Expression schema from grouping params (Null PGtext) infixl 8 Source #

Get JSON value (object field or array element) at a key, as text.

(.#>) :: (json `In` PGJsonType, PGTextArray "(.#>)" path) => Expression schema from grouping params (nullity json) -> Expression schema from grouping params (nullity path) -> Expression schema from grouping params (Null json) infixl 8 Source #

Get JSON value at a specified path.

(.#>>) :: (json `In` PGJsonType, PGTextArray "(.#>>)" path) => Expression schema from grouping params (nullity json) -> Expression schema from grouping params (nullity path) -> Expression schema from grouping params (Null PGtext) infixl 8 Source #

Get JSON value at a specified path as text.

Jsonb operators

(.@>) :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity PGjsonb) -> Condition schema from grouping params infixl 9 Source #

Does the left JSON value contain the right JSON path/value entries at the top level?

(.<@) :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity PGjsonb) -> Condition schema from grouping params infixl 9 Source #

Are the left JSON path/value entries contained at the top level within the right JSON value?

(.?) :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity PGtext) -> Condition schema from grouping params infixl 9 Source #

Does the string exist as a top-level key within the JSON value?

(.?|) :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity (PGvararray (NotNull PGtext))) -> Condition schema from grouping params infixl 9 Source #

Do any of these array strings exist as top-level keys?

(.?&) :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity (PGvararray (NotNull PGtext))) -> Condition schema from grouping params infixl 9 Source #

Do all of these array strings exist as top-level keys?

(.-.) :: key `In` '[PGtext, PGvararray (NotNull PGtext), PGint4, PGint2] => Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity key) -> Expression schema from grouping params (nullity PGjsonb) infixl 6 Source #

Delete a key or keys from a JSON object, or remove an array element.

If the right operand is..

text : Delete keyvalue pair or string element from left operand. Keyvalue pairs are matched based on their key value.

text[] : Delete multiple key/value pairs or string elements from left operand. Key/value pairs are matched based on their key value.

integer : Delete the array element with specified index (Negative integers count from the end). Throws an error if top level container is not an array.

(#-.) :: PGTextArray "(#-.)" arrayty => Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity arrayty) -> Expression schema from grouping params (nullity PGjsonb) infixl 6 Source #

Delete the field or element with specified path (for JSON arrays, negative integers count from the end)

Functions

jsonLit :: ToJSON x => x -> Expression schema from grouping params (nullity PGjson) Source #

Literal JSON

jsonbLit :: ToJSON x => x -> Expression schema from grouping params (nullity PGjsonb) Source #

Literal binary JSON

toJson :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity PGjson) Source #

Returns the value as json. Arrays and composites are converted (recursively) to arrays and objects; otherwise, if there is a cast from the type to json, the cast function will be used to perform the conversion; otherwise, a scalar value is produced. For any scalar type other than a number, a Boolean, or a null value, the text representation will be used, in such a fashion that it is a valid json value.

toJsonb :: Expression schema from grouping params (nullity ty) -> Expression schema from grouping params (nullity PGjsonb) Source #

Returns the value as jsonb. Arrays and composites are converted (recursively) to arrays and objects; otherwise, if there is a cast from the type to json, the cast function will be used to perform the conversion; otherwise, a scalar value is produced. For any scalar type other than a number, a Boolean, or a null value, the text representation will be used, in such a fashion that it is a valid jsonb value.

arrayToJson :: PGArray "arrayToJson" arr => Expression schema from grouping params (nullity arr) -> Expression schema from grouping params (nullity PGjson) Source #

Returns the array as a JSON array. A PostgreSQL multidimensional array becomes a JSON array of arrays.

rowToJson :: Expression schema from grouping params (nullity (PGcomposite ty)) -> Expression schema from grouping params (nullity PGjson) Source #

Returns the row as a JSON object.

jsonBuildArray :: SListI elems => NP (Expression schema from grouping params) elems -> Expression schema from grouping params (nullity PGjson) Source #

Builds a possibly-heterogeneously-typed JSON array out of a variadic argument list.

jsonbBuildArray :: SListI elems => NP (Expression schema from grouping params) elems -> Expression schema from grouping params (nullity PGjsonb) Source #

Builds a possibly-heterogeneously-typed (binary) JSON array out of a variadic argument list.

jsonBuildObject :: All Top elems => NP (Aliased (Expression schema from grouping params)) elems -> Expression schema from grouping params (nullity PGjson) Source #

Builds a possibly-heterogeneously-typed JSON object out of a variadic argument list. The elements of the argument list must alternate between text and values.

jsonbBuildObject :: All Top elems => NP (Aliased (Expression schema from grouping params)) elems -> Expression schema from grouping params (nullity PGjsonb) Source #

Builds a possibly-heterogeneously-typed (binary) JSON object out of a variadic argument list. The elements of the argument list must alternate between text and values.

jsonObject :: PGArrayOf "jsonObject" arr (NotNull PGtext) => Expression schema from grouping params (nullity arr) -> Expression schema from grouping params (nullity PGjson) Source #

Builds a JSON object out of a text array. The array must have either exactly one dimension with an even number of members, in which case they are taken as alternating key/value pairs, or two dimensions such that each inner array has exactly two elements, which are taken as a key/value pair.

jsonbObject :: PGArrayOf "jsonbObject" arr (NotNull PGtext) => Expression schema from grouping params (nullity arr) -> Expression schema from grouping params (nullity PGjsonb) Source #

Builds a binary JSON object out of a text array. The array must have either exactly one dimension with an even number of members, in which case they are taken as alternating key/value pairs, or two dimensions such that each inner array has exactly two elements, which are taken as a key/value pair.

jsonZipObject :: (PGArrayOf "jsonZipObject" keysArray (NotNull PGtext), PGArrayOf "jsonZipObject" valuesArray (NotNull PGtext)) => Expression schema from grouping params (nullity keysArray) -> Expression schema from grouping params (nullity valuesArray) -> Expression schema from grouping params (nullity PGjson) Source #

This is an alternate form of jsonObject that takes two arrays; one for keys and one for values, that are zipped pairwise to create a JSON object.

jsonbZipObject :: (PGArrayOf "jsonbZipObject" keysArray (NotNull PGtext), PGArrayOf "jsonbZipObject" valuesArray (NotNull PGtext)) => Expression schema from grouping params (nullity keysArray) -> Expression schema from grouping params (nullity valuesArray) -> Expression schema from grouping params (nullity PGjsonb) Source #

This is an alternate form of jsonObject that takes two arrays; one for keys and one for values, that are zipped pairwise to create a binary JSON object.

jsonArrayLength :: Expression schema from grouping params (nullity PGjson) -> Expression schema from grouping params (nullity PGint4) Source #

Returns the number of elements in the outermost JSON array.

jsonbArrayLength :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity PGint4) Source #

Returns the number of elements in the outermost binary JSON array.

jsonExtractPath :: SListI elems => Expression schema from grouping params (nullity PGjson) -> NP (Expression schema from grouping params) elems -> Expression schema from grouping params (nullity PGjsonb) Source #

Returns JSON value pointed to by the given path (equivalent to #> operator).

jsonbExtractPath :: SListI elems => Expression schema from grouping params (nullity PGjsonb) -> NP (Expression schema from grouping params) elems -> Expression schema from grouping params (nullity PGjsonb) Source #

Returns JSON value pointed to by the given path (equivalent to #> operator).

jsonExtractPathAsText :: SListI elems => Expression schema from grouping params (nullity PGjson) -> NP (Expression schema from grouping params) elems -> Expression schema from grouping params (nullity PGjson) Source #

Returns JSON value pointed to by the given path (equivalent to #> operator), as text.

jsonbExtractPathAsText :: SListI elems => Expression schema from grouping params (nullity PGjsonb) -> NP (Expression schema from grouping params) elems -> Expression schema from grouping params (nullity PGjsonb) Source #

Returns JSON value pointed to by the given path (equivalent to #> operator), as text.

jsonTypeof :: Expression schema from grouping params (nullity PGjson) -> Expression schema from grouping params (nullity PGtext) Source #

Returns the type of the outermost JSON value as a text string. Possible types are object, array, string, number, boolean, and null.

jsonbTypeof :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity PGtext) Source #

Returns the type of the outermost binary JSON value as a text string. Possible types are object, array, string, number, boolean, and null.

jsonStripNulls :: Expression schema from grouping params (nullity PGjson) -> Expression schema from grouping params (nullity PGjson) Source #

Returns its argument with all object fields that have null values omitted. Other null values are untouched.

jsonbStripNulls :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity PGjsonb) Source #

Returns its argument with all object fields that have null values omitted. Other null values are untouched.

jsonbSet :: PGTextArray "jsonbSet" arr => Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity arr) -> Expression schema from grouping params (nullity PGjsonb) -> Maybe (Expression schema from grouping params (nullity PGbool)) -> Expression schema from grouping params (nullity PGjsonb) Source #

 jsonbSet target path new_value create_missing

Returns target with the section designated by path replaced by new_value, or with new_value added if create_missing is true ( default is true) and the item designated by path does not exist. As with the path orientated operators, negative integers that appear in path count from the end of JSON arrays.

jsonbInsert :: PGTextArray "jsonbInsert" arr => Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity arr) -> Expression schema from grouping params (nullity PGjsonb) -> Maybe (Expression schema from grouping params (nullity PGbool)) -> Expression schema from grouping params (nullity PGjsonb) Source #

 jsonbInsert target path new_value insert_after

Returns target with new_value inserted. If target section designated by path is in a JSONB array, new_value will be inserted before target or after if insert_after is true (default is false). If target section designated by path is in JSONB object, new_value will be inserted only if target does not exist. As with the path orientated operators, negative integers that appear in path count from the end of JSON arrays.

jsonbPretty :: Expression schema from grouping params (nullity PGjsonb) -> Expression schema from grouping params (nullity PGtext) Source #

Returns its argument as indented JSON text.

Aggregation

unsafeAggregate Source #

Arguments

:: ByteString

aggregate function

-> Expression schema from Ungrouped params xty 
-> Expression schema from (Grouped bys) params yty 

escape hatch to define aggregate functions

unsafeAggregateDistinct Source #

Arguments

:: ByteString

aggregate function

-> Expression schema from Ungrouped params xty 
-> Expression schema from (Grouped bys) params yty 

escape hatch to define aggregate functions over distinct values

sum_ Source #

Arguments

:: ty `In` PGNum 
=> Expression schema from Ungrouped params (nullity ty)

what to sum

-> Expression schema from (Grouped bys) params (nullity ty) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: 'Null 'PGnumeric]] ('Grouped bys) params ('Null 'PGnumeric)
  expression = sum_ #col
in printSQL expression
:}
sum("col")

sumDistinct Source #

Arguments

:: ty `In` PGNum 
=> Expression schema from Ungrouped params (nullity ty)

what to sum

-> Expression schema from (Grouped bys) params (nullity ty) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGnumeric]] ('Grouped bys) params (nullity 'PGnumeric)
  expression = sumDistinct #col
in printSQL expression
:}
sum(DISTINCT "col")

class PGAvg ty avg | ty -> avg where Source #

A constraint for PGTypes that you can take averages of and the resulting PGType.

Methods

avg Source #

Arguments

:: Expression schema from Ungrouped params (nullity ty)

what to average

-> Expression schema from (Grouped bys) params (nullity avg) 

avgDistinct Source #

Arguments

:: Expression schema from Ungrouped params (nullity ty)

what to average

-> Expression schema from (Grouped bys) params (nullity avg) 
Instances
PGAvg PGint2 PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGint2) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGint2) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

PGAvg PGint4 PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGint4) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGint4) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

PGAvg PGint8 PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGint8) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGint8) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

PGAvg PGnumeric PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGnumeric) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGnumeric) -> Expression schema from (Grouped bys) params (nullity PGnumeric) Source #

PGAvg PGfloat4 PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGfloat4) -> Expression schema from (Grouped bys) params (nullity PGfloat8) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGfloat4) -> Expression schema from (Grouped bys) params (nullity PGfloat8) Source #

PGAvg PGfloat8 PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGfloat8) -> Expression schema from (Grouped bys) params (nullity PGfloat8) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGfloat8) -> Expression schema from (Grouped bys) params (nullity PGfloat8) Source #

PGAvg PGinterval PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

avg :: Expression schema from Ungrouped params (nullity PGinterval) -> Expression schema from (Grouped bys) params (nullity PGinterval) Source #

avgDistinct :: Expression schema from Ungrouped params (nullity PGinterval) -> Expression schema from (Grouped bys) params (nullity PGinterval) Source #

bitAnd Source #

Arguments

:: int `In` PGIntegral 
=> Expression schema from Ungrouped params (nullity int)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity int) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGint4]] (Grouped bys) params (nullity 'PGint4)
  expression = bitAnd #col
in printSQL expression
:}
bit_and("col")

bitOr Source #

Arguments

:: int `In` PGIntegral 
=> Expression schema from Ungrouped params (nullity int)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity int) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGint4]] (Grouped bys) params (nullity 'PGint4)
  expression = bitOr #col
in printSQL expression
:}
bit_or("col")

boolAnd Source #

Arguments

:: Expression schema from Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity PGbool) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGbool]] (Grouped bys) params (nullity 'PGbool)
  expression = boolAnd #col
in printSQL expression
:}
bool_and("col")

boolOr Source #

Arguments

:: Expression schema from Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity PGbool) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGbool]] (Grouped bys) params (nullity 'PGbool)
  expression = boolOr #col
in printSQL expression
:}
bool_or("col")

bitAndDistinct Source #

Arguments

:: int `In` PGIntegral 
=> Expression schema from Ungrouped params (nullity int)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity int) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGint4]] (Grouped bys) params (nullity 'PGint4)
  expression = bitAndDistinct #col
in printSQL expression
:}
bit_and(DISTINCT "col")

bitOrDistinct Source #

Arguments

:: int `In` PGIntegral 
=> Expression schema from Ungrouped params (nullity int)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity int) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGint4]] (Grouped bys) params (nullity 'PGint4)
  expression = bitOrDistinct #col
in printSQL expression
:}
bit_or(DISTINCT "col")

boolAndDistinct Source #

Arguments

:: Expression schema from Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity PGbool) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGbool]] (Grouped bys) params (nullity 'PGbool)
  expression = boolAndDistinct #col
in printSQL expression
:}
bool_and(DISTINCT "col")

boolOrDistinct Source #

Arguments

:: Expression schema from Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity PGbool) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGbool]] (Grouped bys) params (nullity 'PGbool)
  expression = boolOrDistinct #col
in printSQL expression
:}
bool_or(DISTINCT "col")

countStar :: Expression schema from (Grouped bys) params (NotNull PGint8) Source #

A special aggregation that does not require an input

>>> printSQL countStar
count(*)

count Source #

Arguments

:: Expression schema from Ungrouped params ty

what to count

-> Expression schema from (Grouped bys) params (NotNull PGint8) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity ty]] (Grouped bys) params ('NotNull 'PGint8)
  expression = count #col
in printSQL expression
:}
count("col")

countDistinct Source #

Arguments

:: Expression schema from Ungrouped params ty

what to count

-> Expression schema from (Grouped bys) params (NotNull PGint8) 
>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity ty]] (Grouped bys) params ('NotNull 'PGint8)
  expression = countDistinct #col
in printSQL expression
:}
count(DISTINCT "col")

every Source #

Arguments

:: Expression schema from Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity PGbool) 

synonym for boolAnd

>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGbool]] (Grouped bys) params (nullity 'PGbool)
  expression = every #col
in printSQL expression
:}
every("col")

everyDistinct Source #

Arguments

:: Expression schema from Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity PGbool) 

synonym for boolAndDistinct

>>> :{
let
  expression :: Expression schema '[tab ::: '["col" ::: nullity 'PGbool]] (Grouped bys) params (nullity 'PGbool)
  expression = everyDistinct #col
in printSQL expression
:}
every(DISTINCT "col")

max_ Source #

Arguments

:: Expression schema from Ungrouped params (nullity ty)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity ty) 

minimum and maximum aggregation

maxDistinct Source #

Arguments

:: Expression schema from Ungrouped params (nullity ty)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity ty) 

minimum and maximum aggregation

min_ Source #

Arguments

:: Expression schema from Ungrouped params (nullity ty)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity ty) 

minimum and maximum aggregation

minDistinct Source #

Arguments

:: Expression schema from Ungrouped params (nullity ty)

what to aggregate

-> Expression schema from (Grouped bys) params (nullity ty) 

minimum and maximum aggregation

Types

newtype TypeExpression (schema :: SchemaType) (ty :: NullityType) Source #

TypeExpressions are used in casts and createTable commands.

Instances
Eq (TypeExpression schema ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(==) :: TypeExpression schema ty -> TypeExpression schema ty -> Bool #

(/=) :: TypeExpression schema ty -> TypeExpression schema ty -> Bool #

Ord (TypeExpression schema ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

compare :: TypeExpression schema ty -> TypeExpression schema ty -> Ordering #

(<) :: TypeExpression schema ty -> TypeExpression schema ty -> Bool #

(<=) :: TypeExpression schema ty -> TypeExpression schema ty -> Bool #

(>) :: TypeExpression schema ty -> TypeExpression schema ty -> Bool #

(>=) :: TypeExpression schema ty -> TypeExpression schema ty -> Bool #

max :: TypeExpression schema ty -> TypeExpression schema ty -> TypeExpression schema ty #

min :: TypeExpression schema ty -> TypeExpression schema ty -> TypeExpression schema ty #

Show (TypeExpression schema ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

showsPrec :: Int -> TypeExpression schema ty -> ShowS #

show :: TypeExpression schema ty -> String #

showList :: [TypeExpression schema ty] -> ShowS #

Generic (TypeExpression schema ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Associated Types

type Rep (TypeExpression schema ty) :: * -> * #

Methods

from :: TypeExpression schema ty -> Rep (TypeExpression schema ty) x #

to :: Rep (TypeExpression schema ty) x -> TypeExpression schema ty #

NFData (TypeExpression schema ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

rnf :: TypeExpression schema ty -> () #

type Rep (TypeExpression schema ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

type Rep (TypeExpression schema ty) = D1 (MetaData "TypeExpression" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.4.0.0-GuxxUOwtUmZB6qL3MLEXvb" True) (C1 (MetaCons "UnsafeTypeExpression" PrefixI True) (S1 (MetaSel (Just "renderTypeExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

class PGTyped schema (ty :: NullityType) where Source #

pgtype is a demoted version of a PGType

Minimal complete definition

pgtype

Methods

pgtype :: TypeExpression schema ty Source #

Instances
(KnownNat n, PGTyped schema ty) => PGTyped schema (nullity (PGfixarray n ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity (PGfixarray n ty)) Source #

PGTyped schema ty => PGTyped schema (nullity (PGvararray ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity (PGvararray ty)) Source #

PGTyped schema (nullity PGjsonb) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGjsonb) Source #

PGTyped schema (nullity PGjson) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGjson) Source #

PGTyped schema (nullity PGuuid) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGuuid) Source #

PGTyped schema (nullity PGinterval) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGinterval) Source #

PGTyped schema (nullity PGtimetz) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGtimetz) Source #

PGTyped schema (nullity PGtime) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGtime) Source #

PGTyped schema (nullity PGdate) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGdate) Source #

PGTyped schema (nullity PGtimestamptz) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGtimestamptz) Source #

PGTyped schema (nullity PGtimestamp) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGtimestamp) Source #

PGTyped schema (nullity PGbytea) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGbytea) Source #

(KnownNat n, 1 <= n) => PGTyped schema (nullity (PGvarchar n)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity (PGvarchar n)) Source #

(KnownNat n, 1 <= n) => PGTyped schema (nullity (PGchar n)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity (PGchar n)) Source #

PGTyped schema (nullity PGtext) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGtext) Source #

PGTyped schema (nullity PGfloat8) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGfloat8) Source #

PGTyped schema (nullity PGfloat4) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGfloat4) Source #

PGTyped schema (nullity PGnumeric) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGnumeric) Source #

PGTyped schema (nullity PGint8) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGint8) Source #

PGTyped schema (nullity PGint4) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGint4) Source #

PGTyped schema (nullity PGint2) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGint2) Source #

PGTyped schema (nullity PGbool) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (nullity PGbool) Source #

typedef :: Has alias schema (Typedef ty) => Alias alias -> TypeExpression schema (nullity ty) Source #

The enum or composite type in a Typedef can be expressed by its alias.

typetable :: Has alias schema (Table tab) => Alias alias -> TypeExpression schema (nullity (PGcomposite (TableToRow tab))) Source #

The composite type corresponding to a Table definition can be expressed by its alias.

typeview :: Has alias schema (View view) => Alias alias -> TypeExpression schema (nullity (PGcomposite view)) Source #

The composite type corresponding to a View definition can be expressed by its alias.

bool :: TypeExpression schema (nullity PGbool) Source #

logical Boolean (true/false)

int2 :: TypeExpression schema (nullity PGint2) Source #

signed two-byte integer

smallint :: TypeExpression schema (nullity PGint2) Source #

signed two-byte integer

int4 :: TypeExpression schema (nullity PGint4) Source #

signed four-byte integer

int :: TypeExpression schema (nullity PGint4) Source #

signed four-byte integer

integer :: TypeExpression schema (nullity PGint4) Source #

signed four-byte integer

int8 :: TypeExpression schema (nullity PGint8) Source #

signed eight-byte integer

bigint :: TypeExpression schema (nullity PGint8) Source #

signed eight-byte integer

numeric :: TypeExpression schema (nullity PGnumeric) Source #

arbitrary precision numeric type

float4 :: TypeExpression schema (nullity PGfloat4) Source #

single precision floating-point number (4 bytes)

real :: TypeExpression schema (nullity PGfloat4) Source #

single precision floating-point number (4 bytes)

float8 :: TypeExpression schema (nullity PGfloat8) Source #

double precision floating-point number (8 bytes)

doublePrecision :: TypeExpression schema (nullity PGfloat8) Source #

double precision floating-point number (8 bytes)

text :: TypeExpression schema (nullity PGtext) Source #

variable-length character string

char :: forall n schema nullity. (KnownNat n, 1 <= n) => TypeExpression schema (nullity (PGchar n)) Source #

fixed-length character string

character :: forall n schema nullity. (KnownNat n, 1 <= n) => TypeExpression schema (nullity (PGchar n)) Source #

fixed-length character string

varchar :: forall n schema nullity. (KnownNat n, 1 <= n) => TypeExpression schema (nullity (PGvarchar n)) Source #

variable-length character string

characterVarying :: forall n schema nullity. (KnownNat n, 1 <= n) => TypeExpression schema (nullity (PGvarchar n)) Source #

variable-length character string

bytea :: TypeExpression schema (nullity PGbytea) Source #

binary data ("byte array")

timestamp :: TypeExpression schema (nullity PGtimestamp) Source #

date and time (no time zone)

timestampWithTimeZone :: TypeExpression schema (nullity PGtimestamptz) Source #

date and time, including time zone

date :: TypeExpression schema (nullity PGdate) Source #

calendar date (year, month, day)

time :: TypeExpression schema (nullity PGtime) Source #

time of day (no time zone)

timeWithTimeZone :: TypeExpression schema (nullity PGtimetz) Source #

time of day, including time zone

interval :: TypeExpression schema (nullity PGinterval) Source #

time span

uuid :: TypeExpression schema (nullity PGuuid) Source #

universally unique identifier

inet :: TypeExpression schema (nullity PGinet) Source #

IPv4 or IPv6 host address

json :: TypeExpression schema (nullity PGjson) Source #

textual JSON data

jsonb :: TypeExpression schema (nullity PGjsonb) Source #

binary JSON data, decomposed

vararray :: TypeExpression schema pg -> TypeExpression schema (nullity (PGvararray pg)) Source #

variable length array

fixarray :: forall n schema nullity pg. KnownNat n => TypeExpression schema pg -> TypeExpression schema (nullity (PGfixarray n pg)) Source #

fixed length array

>>> renderTypeExpression (fixarray @2 json)
"json[2]"

Re-export

(&) :: a -> (a -> b) -> b infixl 1 #

& is a reverse application operator. This provides notational convenience. Its precedence is one higher than that of the forward application operator $, which allows & to be nested in $.

>>> 5 & (+1) & show
"6"

Since: base-4.8.0.0

data NP (a :: k -> *) (b :: [k]) :: forall k. (k -> *) -> [k] -> * where #

An n-ary product.

The product is parameterized by a type constructor f and indexed by a type-level list xs. The length of the list determines the number of elements in the product, and if the i-th element of the list is of type x, then the i-th element of the product is of type f x.

The constructor names are chosen to resemble the names of the list constructors.

Two common instantiations of f are the identity functor I and the constant functor K. For I, the product becomes a heterogeneous list, where the type-level list describes the types of its components. For K a, the product becomes a homogeneous list, where the contents of the type-level list are ignored, but its length still specifies the number of elements.

In the context of the SOP approach to generic programming, an n-ary product describes the structure of the arguments of a single data constructor.

Examples:

I 'x'    :* I True  :* Nil  ::  NP I       '[ Char, Bool ]
K 0      :* K 1     :* Nil  ::  NP (K Int) '[ Char, Bool ]
Just 'x' :* Nothing :* Nil  ::  NP Maybe   '[ Char, Bool ]

Constructors

Nil :: NP a ([] :: [k]) 
(:*) :: NP a (x ': xs) infixr 5 
Instances
(Has table from columns, Has column columns ty, GroupedBy table column bys) => IsQualified table column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) Source #

(Has table from columns, Has column columns ty) => IsQualified table column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias table -> Alias column -> NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) Source #

(Has rel rels cols, Has col cols ty, bys ~ ((,) rel col ': ([] :: [(Symbol, Symbol)]))) => IsQualified rel col (NP (By rels) bys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

(!) :: Alias rel -> Alias col -> NP (By rels) bys Source #

HTrans (NP :: (k1 -> *) -> [k1] -> *) (NP :: (k2 -> *) -> [k2] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

htrans :: AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys #

hcoerce :: (AllZipN (Prod NP) (LiftedCoercible f g) xs ys, HTrans NP NP) => NP f xs -> NP g ys #

HPure (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hpure :: SListIN NP xs => (forall (a :: k0). f a) -> NP f xs #

hcpure :: AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs #

HAp (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hap :: Prod NP (f -.-> g) xs -> NP f xs -> NP g xs #

HCollapse (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hcollapse :: SListIN NP xs => NP (K a) xs -> CollapseTo NP a #

HTraverse_ (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hctraverse_ :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () #

htraverse_ :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () #

HSequence (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hsequence' :: (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) #

hctraverse' :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

htraverse' :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) #

(KnownSymbol alias, tys ~ ((alias ::: ty) ': ([] :: [(Symbol, k)]))) => Aliasable alias (expression ty) (NP (Aliased expression) tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

as :: expression ty -> Alias alias -> NP (Aliased expression) tys Source #

aliases ~ (alias ': ([] :: [Symbol])) => IsLabel alias (NP Alias aliases) # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

fromLabel :: NP Alias aliases #

(HasUnique table from columns, Has column columns ty, GroupedBy table column bys) => IsLabel column (NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from (Grouped bys) params)) ((column ::: ty) ': []) #

(HasUnique table from columns, Has column columns ty) => IsLabel column (NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema from Ungrouped params)) ((column ::: ty) ': []) #

(HasUnique rel rels cols, Has col cols ty, bys ~ ((,) rel col ': ([] :: [(Symbol, Symbol)]))) => IsLabel col (NP (By rels) bys) # 
Instance details

Defined in Squeal.PostgreSQL.Query

Methods

fromLabel :: NP (By rels) bys #

labels ~ (label ': ([] :: [Symbol])) => IsPGlabel label (NP PGlabel labels) Source # 
Instance details

Defined in Squeal.PostgreSQL.Schema

Methods

label :: NP PGlabel labels Source #

All (Compose Eq f) xs => Eq (NP f xs) 
Instance details

Defined in Generics.SOP.NP

Methods

(==) :: NP f xs -> NP f xs -> Bool #

(/=) :: NP f xs -> NP f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) 
Instance details

Defined in Generics.SOP.NP

Methods

compare :: NP f xs -> NP f xs -> Ordering #

(<) :: NP f xs -> NP f xs -> Bool #

(<=) :: NP f xs -> NP f xs -> Bool #

(>) :: NP f xs -> NP f xs -> Bool #

(>=) :: NP f xs -> NP f xs -> Bool #

max :: NP f xs -> NP f xs -> NP f xs #

min :: NP f xs -> NP f xs -> NP f xs #

All (Compose Show f) xs => Show (NP f xs) 
Instance details

Defined in Generics.SOP.NP

Methods

showsPrec :: Int -> NP f xs -> ShowS #

show :: NP f xs -> String #

showList :: [NP f xs] -> ShowS #

All (Compose NFData f) xs => NFData (NP f xs)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.NP

Methods

rnf :: NP f xs -> () #

type AllZipN (NP :: (k -> *) -> [k] -> *) (c :: a -> b -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllZipN (NP :: (k -> *) -> [k] -> *) (c :: a -> b -> Constraint) = AllZip c
type Same (NP :: (k1 -> *) -> [k1] -> *) 
Instance details

Defined in Generics.SOP.NP

type Same (NP :: (k1 -> *) -> [k1] -> *) = (NP :: (k2 -> *) -> [k2] -> *)
type Prod (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

type Prod (NP :: (k -> *) -> [k] -> *) = (NP :: (k -> *) -> [k] -> *)
type UnProd (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

type UnProd (NP :: (k -> *) -> [k] -> *) = (NS :: (k -> *) -> [k] -> *)
type SListIN (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

type SListIN (NP :: (k -> *) -> [k] -> *) = (SListI :: [k] -> Constraint)
type CollapseTo (NP :: (k -> *) -> [k] -> *) a 
Instance details

Defined in Generics.SOP.NP

type CollapseTo (NP :: (k -> *) -> [k] -> *) a = [a]
type AllN (NP :: (k -> *) -> [k] -> *) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllN (NP :: (k -> *) -> [k] -> *) (c :: k -> Constraint) = All c