squeal-postgresql-0.3.2.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) (relations :: RelationsType) (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 relation relations columns, Has column columns ty, GroupedBy relation column bys) => IsQualified relation column (NP (Aliased (Expression schema relations (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias relation -> Alias column -> Expression schema relations Ungrouped params ty Source #

Has field fields ty => IsLabel field (Expression schema relation grouping params (nullity (PGcomposite fields)) -> Expression schema relation grouping params (Null ty)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Expression schema relation grouping params (nullity (PGcomposite fields)) -> Expression schema relation grouping params (Null ty) #

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: Expression schema relations Ungrouped params ty #

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Associated Types

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

Methods

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

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

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

Concatenate two jsonb values into a new jsonb value.

Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

type Rep (Expression schema relations grouping params ty) = D1 (MetaData "Expression" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.3.2.0-C1DUTRQBZ7xFTzLk0tObU0" 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 (PGTypeOf ty) -> Expression schema relations 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 (PGTypeOf ty) -> Expression schema relations grouping (ty' ': params) ty Source #

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

param Source #

Arguments

:: (PGTyped schema (PGTypeOf ty), HasParameter n schema params ty) 
=> Expression schema relations 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 relations grouping params (Null ty)]

NULLs may be present

-> Expression schema relations grouping params (NotNull ty)

NULL is absent

-> Expression schema relations grouping params (NotNull ty) 

return the leftmost value which is not NULL

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

fromNull Source #

Arguments

:: Expression schema relations grouping params (NotNull ty)

what to convert NULL to

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

analagous to fromMaybe using COALESCE

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

isNull Source #

Arguments

:: Expression schema relations grouping params (Null ty)

possibly NULL

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

isNotNull Source #

Arguments

:: Expression schema relations grouping params (Null ty)

possibly NULL

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

matchNull Source #

Arguments

:: Expression schema relations grouping params nullty

what to convert NULL to

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

function to perform when NULL is absent

-> Expression schema relations grouping params (Null ty) 
-> Expression schema relations 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 relations grouping params (NotNull ty)

NULL is absent

-> Expression schema relations grouping params (NotNull ty)

NULL is absent

-> Expression schema relations 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 relations grouping params (Null ty)]

array elements

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

row Source #

Arguments

:: SListI (Nulls fields) 
=> NP (Aliased (Expression schema relations grouping params)) (Nulls fields)

zero or more expressions for the row field values

-> Expression schema relations grouping params (nullity (PGcomposite fields)) 

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" ::: 'PGfloat8, "imaginary" ::: 'PGfloat8]
>>> let i = row (0 `as` #real :* 1 `as` #imaginary) :: Expression '[] '[] 'Ungrouped '[] ('NotNull Complex)
>>> printSQL i
ROW(0, 1)

Functions

unsafeBinaryOp Source #

Arguments

:: ByteString

operator

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

unsafeUnaryOp Source #

Arguments

:: ByteString

operator

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

unsafeFunction Source #

Arguments

:: ByteString

function

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

unsafeVariadicFunction Source #

Arguments

:: SListI elems 
=> ByteString

function

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

Helper for defining variadic functions.

atan2_ Source #

Arguments

:: PGFloating float 
=> Expression schema relations grouping params (nullity float)

numerator

-> Expression schema relations grouping params (nullity float)

denominator

-> Expression schema relations grouping params (nullity float) 
>>> :{
let
  expression :: Expression schema relations 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 relations grouping params (nullity ty0)

value to convert

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

quot_ Source #

Arguments

:: PGIntegral int 
=> Expression schema relations grouping params (nullity int)

numerator

-> Expression schema relations grouping params (nullity int)

denominator

-> Expression schema relations grouping params (nullity int) 

integer division, truncates the result

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

rem_ Source #

Arguments

:: PGIntegral int 
=> Expression schema relations grouping params (nullity int)

numerator

-> Expression schema relations grouping params (nullity int)

denominator

-> Expression schema relations grouping params (nullity int) 

remainder upon integer division

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

trunc Source #

Arguments

:: PGFloating frac 
=> Expression schema relations grouping params (nullity frac)

fractional number

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

round_ Source #

Arguments

:: PGFloating frac 
=> Expression schema relations grouping params (nullity frac)

fractional number

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

ceiling_ Source #

Arguments

:: PGFloating frac 
=> Expression schema relations grouping params (nullity frac)

fractional number

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

greatest Source #

Arguments

:: Expression schema relations grouping params nullty

needs at least 1 argument

-> [Expression schema relations grouping params nullty]

or more

-> Expression schema relations 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 relations grouping params nullty

needs at least 1 argument

-> [Expression schema relations grouping params nullty]

or more

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

Conditions

type Condition schema relations grouping params = Expression schema relations grouping params (NotNull PGbool) Source #

A Condition is a boolean valued Expression. While SQL allows conditions to have NULL, Squeal instead chooses to disallow NULL, forcing one to handle the case of NULL explicitly to produce a Condition.

true :: Condition schema relations grouping params Source #

>>> printSQL true
TRUE

false :: Condition schema relations grouping params Source #

>>> printSQL false
FALSE

not_ :: Condition schema relations grouping params -> Condition schema relations grouping params Source #

>>> printSQL $ not_ true
(NOT TRUE)

(.&&) :: Condition schema relations grouping params -> Condition schema relations grouping params -> Condition schema relations grouping params Source #

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

(.||) :: Condition schema relations grouping params -> Condition schema relations grouping params -> Condition schema relations grouping params Source #

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

caseWhenThenElse Source #

Arguments

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

whens and thens

-> Expression schema relations grouping params ty

else

-> Expression schema relations grouping params ty 
>>> :{
let
  expression :: Expression schema relations 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 relations grouping params 
-> Expression schema relations grouping params ty

then

-> Expression schema relations grouping params ty

else

-> Expression schema relations grouping params ty 
>>> :{
let
  expression :: Expression schema relations 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 relations grouping params (nullity ty)

lhs

-> Expression schema relations grouping params (nullity ty)

rhs

-> Expression schema relations grouping params (nullity PGbool) 

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

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

(./=) infix 4 Source #

Arguments

:: Expression schema relations grouping params (nullity ty)

lhs

-> Expression schema relations grouping params (nullity ty)

rhs

-> Expression schema relations grouping params (nullity PGbool) 
>>> printSQL $ notNull true ./= null_
(TRUE <> NULL)

(.>=) infix 4 Source #

Arguments

:: Expression schema relations grouping params (nullity ty)

lhs

-> Expression schema relations grouping params (nullity ty)

rhs

-> Expression schema relations grouping params (nullity PGbool) 
>>> printSQL $ notNull true .>= null_
(TRUE >= NULL)

(.<) infix 4 Source #

Arguments

:: Expression schema relations grouping params (nullity ty)

lhs

-> Expression schema relations grouping params (nullity ty)

rhs

-> Expression schema relations grouping params (nullity PGbool) 
>>> printSQL $ notNull true .< null_
(TRUE < NULL)

(.<=) infix 4 Source #

Arguments

:: Expression schema relations grouping params (nullity ty)

lhs

-> Expression schema relations grouping params (nullity ty)

rhs

-> Expression schema relations grouping params (nullity PGbool) 
>>> printSQL $ notNull true .<= null_
(TRUE <= NULL)

(.>) infix 4 Source #

Arguments

:: Expression schema relations grouping params (nullity ty)

lhs

-> Expression schema relations grouping params (nullity ty)

rhs

-> Expression schema relations grouping params (nullity PGbool) 
>>> printSQL $ notNull true .> null_
(TRUE > NULL)

Time

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

>>> printSQL currentDate
CURRENT_DATE

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

>>> printSQL currentTime
CURRENT_TIME

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

>>> printSQL currentTimestamp
CURRENT_TIMESTAMP

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

>>> printSQL localTime
LOCALTIME

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

>>> printSQL localTimestamp
LOCALTIMESTAMP

Text

lower Source #

Arguments

:: Expression schema relations grouping params (nullity PGtext)

string to lower case

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

upper Source #

Arguments

:: Expression schema relations grouping params (nullity PGtext)

string to upper case

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

charLength Source #

Arguments

:: Expression schema relations grouping params (nullity PGtext)

string to measure

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

like Source #

Arguments

:: Expression schema relations grouping params (nullity PGtext)

string

-> Expression schema relations grouping params (nullity PGtext)

pattern

-> Expression schema relations 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 or jsonb operators

type family PGarray name arr :: Constraint where ... Source #

Ensure a type is a valid array type.

Equations

PGarray name (PGvararray x) = () 
PGarray name (PGfixarray n x) = () 
PGarray name val = TypeError ((((Text name :<>: Text ": Unsatisfied PGarray constraint. Expected either: ") :$$: (Text " \8226 " :<>: ErrPGvararrayOf (Placeholder PGType))) :$$: (Text " \8226 " :<>: ErrPGfixarrayOf (Placeholder PGType))) :$$: (Text "But got: " :<>: ShowType val)) 

type family PGarrayOf name arr ty :: Constraint where ... Source #

Ensure a type is a valid array type with a specific element type.

Equations

PGarrayOf name (PGvararray x) ty = x ~ ty 
PGarrayOf name (PGfixarray n x) ty = x ~ ty 
PGarrayOf name val ty = TypeError ((((Text name :<>: Text "Unsatisfied PGarrayOf constraint. Expected either: ") :$$: (Text " \8226 " :<>: ErrPGvararrayOf (ShowType ty))) :$$: (Text " \8226 " :<>: ErrPGfixarrayOf (ShowType ty))) :$$: (Text "But got: " :<>: ShowType val)) 

type PGjsonKey key = key `In` '[PGint2, PGint4, PGtext] Source #

Is a type a valid JSON key?

type PGjson_ json = json `In` '[PGjson, PGjsonb] Source #

Is a type a valid JSON type?

(.->) :: (PGjson_ json, PGjsonKey key) => Expression schema relations grouping params (nullity json) -> Expression schema relations grouping params (nullity key) -> Expression schema relations grouping params (Null json) Source #

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

(.->>) :: (PGjson_ json, PGjsonKey key) => Expression schema relations grouping params (nullity json) -> Expression schema relations grouping params (nullity key) -> Expression schema relations grouping params (Null PGtext) Source #

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

(.#>) :: (PGjson_ json, PGtextArray "(.#>)" path) => Expression schema relations grouping params (nullity json) -> Expression schema relations grouping params (nullity path) -> Expression schema relations grouping params (Null json) Source #

Get JSON value at a specified path.

(.#>>) :: (PGjson_ json, PGtextArray "(.#>>)" path) => Expression schema relations grouping params (nullity json) -> Expression schema relations grouping params (nullity path) -> Expression schema relations grouping params (Null PGtext) Source #

Get JSON value at a specified path as text.

jsonb only operators

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

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

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

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

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

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

(.?|) :: Expression schema relations grouping params (nullity PGjsonb) -> Expression schema relations grouping params (nullity (PGvararray PGtext)) -> Condition schema relations grouping params Source #

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

(.?&) :: Expression schema relations grouping params (nullity PGjsonb) -> Expression schema relations grouping params (nullity (PGvararray PGtext)) -> Condition schema relations grouping params Source #

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

(.-.) :: key `In` '[PGtext, PGvararray PGtext, PGint4, PGint2] => Expression schema relations grouping params (nullity PGjsonb) -> Expression schema relations grouping params (nullity key) -> Expression schema relations grouping params (nullity PGjsonb) 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 relations grouping params (nullity PGjsonb) -> Expression schema relations grouping params (nullity arrayty) -> Expression schema relations grouping params (nullity PGjsonb) Source #

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

Functions

jsonLit :: Value -> Expression schema relations grouping params (nullity PGjson) Source #

Literal JSON

jsonbLit :: Value -> Expression schema relations grouping params (nullity PGjsonb) Source #

Literal binary JSON

toJson :: Expression schema relations grouping params (nullity ty) -> Expression schema relations 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 relations grouping params (nullity ty) -> Expression schema relations 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 relations grouping params (nullity arr) -> Expression schema relations 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 relations grouping params (nullity (PGcomposite ty)) -> Expression schema relations grouping params (nullity PGjson) Source #

Returns the row as a JSON object.

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

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

jsonbBuildArray :: SListI elems => NP (Expression schema relations grouping params) elems -> Expression schema relations 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 relations grouping params)) elems -> Expression schema relations 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 relations grouping params)) elems -> Expression schema relations 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 PGtext => Expression schema relations grouping params (nullity arr) -> Expression schema relations 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 PGtext => Expression schema relations grouping params (nullity arr) -> Expression schema relations 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 PGtext, PGarrayOf "jsonZipObject" valuesArray PGtext) => Expression schema relations grouping params (nullity keysArray) -> Expression schema relations grouping params (nullity valuesArray) -> Expression schema relations 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 PGtext, PGarrayOf "jsonbZipObject" valuesArray PGtext) => Expression schema relations grouping params (nullity keysArray) -> Expression schema relations grouping params (nullity valuesArray) -> Expression schema relations 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 relations grouping params (nullity PGjson) -> Expression schema relations grouping params (nullity PGint4) Source #

Returns the number of elements in the outermost JSON array.

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

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

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

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

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

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

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

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

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

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

jsonObjectKeys :: Expression schema relations grouping params (nullity PGjson) -> Expression schema relations grouping params (nullity PGtext) Source #

Returns set of keys in the outermost JSON object.

jsonbObjectKeys :: Expression schema relations grouping params (nullity PGjsonb) -> Expression schema relations grouping params (nullity PGtext) Source #

Returns set of keys in the outermost JSON object.

jsonTypeof :: Expression schema relations grouping params (nullity PGjson) -> Expression schema relations 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 relations grouping params (nullity PGjsonb) -> Expression schema relations 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 relations grouping params (nullity PGjson) -> Expression schema relations 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 relations grouping params (nullity PGjsonb) -> Expression schema relations 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 relations grouping params (nullity PGjsonb) -> Expression schema relations grouping params (nullity arr) -> Expression schema relations grouping params (nullity PGjsonb) -> Maybe (Expression schema relations grouping params (nullity PGbool)) -> Expression schema relations 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 relations grouping params (nullity PGjsonb) -> Expression schema relations grouping params (nullity arr) -> Expression schema relations grouping params (nullity PGjsonb) -> Maybe (Expression schema relations grouping params (nullity PGbool)) -> Expression schema relations 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 relations grouping params (nullity PGjsonb) -> Expression schema relations grouping params (nullity PGtext) Source #

Returns its argument as indented JSON text.

Aggregation

unsafeAggregate Source #

Arguments

:: ByteString

aggregate function

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

escape hatch to define aggregate functions

unsafeAggregateDistinct Source #

Arguments

:: ByteString

aggregate function

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

escape hatch to define aggregate functions over distinct values

sum_ Source #

Arguments

:: PGNum ty 
=> Expression schema relations Ungrouped params (nullity ty)

what to sum

-> Expression schema relations (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

:: PGNum ty 
=> Expression schema relations Ungrouped params (nullity ty)

what to sum

-> Expression schema relations (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 relations Ungrouped params (nullity ty)

what to average

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

avgDistinct Source #

Arguments

:: Expression schema relations Ungrouped params (nullity ty)

what to average

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

PGAvg PGint4 PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

PGAvg PGint8 PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

PGAvg PGnumeric PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

PGAvg PGfloat4 PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

PGAvg PGfloat8 PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

PGAvg PGinterval PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

bitAnd Source #

Arguments

:: PGIntegral int 
=> Expression schema relations Ungrouped params (nullity int)

what to aggregate

-> Expression schema relations (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

:: PGIntegral int 
=> Expression schema relations Ungrouped params (nullity int)

what to aggregate

-> Expression schema relations (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 relations Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema relations (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 relations Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema relations (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

:: PGIntegral int 
=> Expression schema relations Ungrouped params (nullity int)

what to aggregate

-> Expression schema relations (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

:: PGIntegral int 
=> Expression schema relations Ungrouped params (nullity int)

what to aggregate

-> Expression schema relations (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 relations Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema relations (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 relations Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema relations (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 relations (Grouped bys) params (NotNull PGint8) Source #

A special aggregation that does not require an input

>>> printSQL countStar
count(*)

count Source #

Arguments

:: Expression schema relations Ungrouped params ty

what to count

-> Expression schema relations (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 relations Ungrouped params ty

what to count

-> Expression schema relations (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 relations Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema relations (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 relations Ungrouped params (nullity PGbool)

what to aggregate

-> Expression schema relations (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 relations Ungrouped params (nullity ty)

what to aggregate

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

minimum and maximum aggregation

maxDistinct Source #

Arguments

:: Expression schema relations Ungrouped params (nullity ty)

what to aggregate

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

minimum and maximum aggregation

min_ Source #

Arguments

:: Expression schema relations Ungrouped params (nullity ty)

what to aggregate

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

minimum and maximum aggregation

minDistinct Source #

Arguments

:: Expression schema relations Ungrouped params (nullity ty)

what to aggregate

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

minimum and maximum aggregation

Types

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

TypeExpressions are used in casts and createTable commands.

Instances
Has alias schema (Typedef ty) => IsLabel alias (TypeExpression schema ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: TypeExpression schema ty #

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.3.2.0-C1DUTRQBZ7xFTzLk0tObU0" True) (C1 (MetaCons "UnsafeTypeExpression" PrefixI True) (S1 (MetaSel (Just "renderTypeExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

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

pgtype is a demoted version of a PGType

Minimal complete definition

pgtype

Methods

pgtype :: TypeExpression schema ty Source #

Instances
PGTyped schema PGjsonb Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGjson Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGuuid Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGinterval Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGtimetz Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGtime Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGdate Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGtimestamptz Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGtimestamp Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGbytea Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGtext Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGfloat8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGfloat4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGnumeric Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGint8 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGint4 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGint2 Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

PGTyped schema PGbool Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

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

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (PGvararray ty) Source #

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

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (PGvarchar n) Source #

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

Defined in Squeal.PostgreSQL.Expression

Methods

pgtype :: TypeExpression schema (PGchar n) Source #

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

Defined in Squeal.PostgreSQL.Expression

Methods

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

bool :: TypeExpression schema PGbool Source #

logical Boolean (true/false)

int2 :: TypeExpression schema PGint2 Source #

signed two-byte integer

smallint :: TypeExpression schema PGint2 Source #

signed two-byte integer

int4 :: TypeExpression schema PGint4 Source #

signed four-byte integer

int :: TypeExpression schema PGint4 Source #

signed four-byte integer

integer :: TypeExpression schema PGint4 Source #

signed four-byte integer

int8 :: TypeExpression schema PGint8 Source #

signed eight-byte integer

bigint :: TypeExpression schema PGint8 Source #

signed eight-byte integer

numeric :: TypeExpression schema PGnumeric Source #

arbitrary precision numeric type

float4 :: TypeExpression schema PGfloat4 Source #

single precision floating-point number (4 bytes)

real :: TypeExpression schema PGfloat4 Source #

single precision floating-point number (4 bytes)

float8 :: TypeExpression schema PGfloat8 Source #

double precision floating-point number (8 bytes)

doublePrecision :: TypeExpression schema PGfloat8 Source #

double precision floating-point number (8 bytes)

text :: TypeExpression schema PGtext Source #

variable-length character string

char :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression schema (PGchar n) Source #

fixed-length character string

character :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression schema (PGchar n) Source #

fixed-length character string

varchar :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression schema (PGvarchar n) Source #

variable-length character string

characterVarying :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression schema (PGvarchar n) Source #

variable-length character string

bytea :: TypeExpression schema PGbytea Source #

binary data ("byte array")

timestamp :: TypeExpression schema PGtimestamp Source #

date and time (no time zone)

timestampWithTimeZone :: TypeExpression schema PGtimestamptz Source #

date and time, including time zone

date :: TypeExpression schema PGdate Source #

calendar date (year, month, day)

time :: TypeExpression schema PGtime Source #

time of day (no time zone)

timeWithTimeZone :: TypeExpression schema PGtimetz Source #

time of day, including time zone

uuid :: TypeExpression schema PGuuid Source #

universally unique identifier

inet :: TypeExpression schema PGinet Source #

IPv4 or IPv6 host address

json :: TypeExpression schema PGjson Source #

textual JSON data

jsonb :: TypeExpression schema PGjsonb Source #

binary JSON data, decomposed

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

variable length array

fixarray :: KnownNat n => proxy n -> TypeExpression schema pg -> TypeExpression schema (PGfixarray n pg) Source #

fixed length array

>>> renderTypeExpression (fixarray (Proxy @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 relation relations columns, Has column columns ty, GroupedBy relation column bys) => IsQualified relation column (NP (Aliased (Expression schema relations (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

(!) :: Alias relation -> Alias column -> NP (Aliased (Expression schema relations 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 relation relations columns, Has column columns ty, GroupedBy relation column bys) => IsLabel column (NP (Aliased (Expression schema relations (Grouped bys) params)) ((column ::: ty) ': ([] :: [(Symbol, NullityType)]))) # 
Instance details

Defined in Squeal.PostgreSQL.Expression

Methods

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

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

Defined in Squeal.PostgreSQL.Expression

Methods

fromLabel :: NP (Aliased (Expression schema relations 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