squeal-postgresql-0.1.1.4: 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 (tables :: TablesType) (grouping :: Grouping) (params :: [ColumnType]) (ty :: ColumnType) Source #

Expressions are used in a variety of contexts, such as in the target list of the select command, as new column values in insertInto 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

(HasTable table tables columns, HasColumn column columns ty, GroupedBy table column bys) => IsTableColumn table column (Expression tables (Grouped bys) params ty) Source # 

Methods

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

(HasTable table tables columns, HasColumn column columns ty) => IsTableColumn table column (Expression tables Ungrouped params ty) Source # 

Methods

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

(HasUnique ColumnsType table tables columns, HasColumn column columns ty, GroupedBy table column bys) => IsLabel column (Expression tables (Grouped bys) params ty) Source # 

Methods

fromLabel :: Expression tables (Grouped bys) params ty #

(HasColumn column columns ty, HasUnique ColumnsType table tables columns) => IsLabel column (Expression tables Ungrouped params ty) Source # 

Methods

fromLabel :: Expression tables Ungrouped params ty #

Eq (Expression tables grouping params ty) Source # 

Methods

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

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

(PGNum ty, PGFloating ty) => Floating (Expression tables grouping params (Required (nullity ty))) Source # 

Methods

pi :: Expression tables grouping params (Required (nullity ty)) #

exp :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

log :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

sqrt :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

(**) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

logBase :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

sin :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

cos :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

tan :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

asin :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

acos :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

atan :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

sinh :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

cosh :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

tanh :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

asinh :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

acosh :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

atanh :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

log1p :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

expm1 :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

log1pexp :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

log1mexp :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

(PGNum ty, PGFloating ty) => Fractional (Expression tables grouping params (Required (nullity ty))) Source # 

Methods

(/) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

recip :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

fromRational :: Rational -> Expression tables grouping params (Required (nullity ty)) #

PGNum ty => Num (Expression tables grouping params (Required (nullity ty))) Source # 

Methods

(+) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

(-) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

(*) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

negate :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

abs :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

signum :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) #

fromInteger :: Integer -> Expression tables grouping params (Required (nullity ty)) #

Ord (Expression tables grouping params ty) Source # 

Methods

compare :: Expression tables grouping params ty -> Expression tables grouping params ty -> Ordering #

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

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

(>) :: Expression tables grouping params ty -> Expression tables grouping params ty -> Bool #

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

max :: Expression tables grouping params ty -> Expression tables grouping params ty -> Expression tables grouping params ty #

min :: Expression tables grouping params ty -> Expression tables grouping params ty -> Expression tables grouping params ty #

Show (Expression tables grouping params ty) Source # 

Methods

showsPrec :: Int -> Expression tables grouping params ty -> ShowS #

show :: Expression tables grouping params ty -> String #

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

IsString (Expression tables grouping params (Required (nullity PGtext))) Source # 

Methods

fromString :: String -> Expression tables grouping params (Required (nullity PGtext)) #

Generic (Expression tables grouping params ty) Source # 

Associated Types

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

Methods

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

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

Monoid (Expression tables grouping params (Required (nullity PGtext))) Source # 

Methods

mempty :: Expression tables grouping params (Required (nullity PGtext)) #

mappend :: Expression tables grouping params (Required (nullity PGtext)) -> Expression tables grouping params (Required (nullity PGtext)) -> Expression tables grouping params (Required (nullity PGtext)) #

mconcat :: [Expression tables grouping params (Required (nullity PGtext))] -> Expression tables grouping params (Required (nullity PGtext)) #

NFData (Expression tables grouping params ty) Source # 

Methods

rnf :: Expression tables grouping params ty -> () #

type Rep (Expression tables grouping params ty) Source # 
type Rep (Expression tables grouping params ty) = D1 * (MetaData "Expression" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.1.1.4-k5IDJoGvjq2Crr3wWyEON" True) (C1 * (MetaCons "UnsafeExpression" PrefixI True) (S1 * (MetaSel (Just Symbol "renderExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

class (PGTyped (BaseType ty), KnownNat n) => HasParameter (n :: Nat) params ty | 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

param :: Expression tables grouping params ty Source #

Instances

(KnownNat n, HasParameter ((-) n 1) params ty) => HasParameter n ((:) ColumnType ty' params) ty Source # 

Methods

param :: Expression tables grouping ((ColumnType ': ty') params) ty Source #

PGTyped (BaseType ty1) => HasParameter 1 ((:) ColumnType ty1 tys) ty1 Source # 

Methods

param :: Expression tables grouping ((ColumnType ': ty1) tys) ty1 Source #

class KnownSymbol column => HasColumn column columns ty | column columns -> ty where Source #

A HasColumn constraint indicates an unqualified column reference. getColumn can only be unambiguous when the TableExpression the column references is unique, in which case the column may be referenced using -XOverloadedLabels. Otherwise, combined with a HasTable constraint, the qualified column reference operator ! may be used.

Methods

getColumn :: HasUnique table tables columns => Alias column -> Expression tables Ungrouped params ty Source #

Instances

(KnownSymbol column, HasColumn column table ty) => HasColumn column ((:) (Symbol, ColumnType) ty' table) ty Source # 

Methods

getColumn :: HasUnique ColumnsType table tables (((Symbol, ColumnType) ': ty') table) => Alias column -> Expression tables Ungrouped params ty Source #

KnownSymbol column => HasColumn column ((:) (Symbol, ColumnType) ((:::) ColumnType column (optionality ty)) tys) (Required ty) Source # 

Methods

getColumn :: HasUnique ColumnsType table tables (((Symbol, ColumnType) ': (ColumnType ::: column) (optionality ty)) tys) => Alias column -> Expression tables Ungrouped params (Required ty) Source #

data Column (columns :: ColumnsType) (columnty :: (Symbol, ColumnType)) where Source #

A Column is a witness to a HasColumn constraint. It's used in unique and other TableConstraints to witness a subcolumns relationship.

Constructors

Column :: HasColumn column columns ty => Alias column -> Column columns (column ::: ty) 

Instances

Eq (Column columns columnty) Source # 

Methods

(==) :: Column columns columnty -> Column columns columnty -> Bool #

(/=) :: Column columns columnty -> Column columns columnty -> Bool #

Ord (Column columns columnty) Source # 

Methods

compare :: Column columns columnty -> Column columns columnty -> Ordering #

(<) :: Column columns columnty -> Column columns columnty -> Bool #

(<=) :: Column columns columnty -> Column columns columnty -> Bool #

(>) :: Column columns columnty -> Column columns columnty -> Bool #

(>=) :: Column columns columnty -> Column columns columnty -> Bool #

max :: Column columns columnty -> Column columns columnty -> Column columns columnty #

min :: Column columns columnty -> Column columns columnty -> Column columns columnty #

Show (Column columns columnty) Source # 

Methods

showsPrec :: Int -> Column columns columnty -> ShowS #

show :: Column columns columnty -> String #

showList :: [Column columns columnty] -> ShowS #

renderColumn :: Column columns columnty -> ByteString Source #

Render a Column.

class (KnownSymbol table, KnownSymbol column) => GroupedBy table column bys where Source #

A GroupedBy constraint indicates that a table qualified column is a member of the auxiliary namespace created by GROUP BY clauses and thus, may be called in an output Expression without aggregating.

Methods

getGroup1 :: (HasUnique table tables columns, HasColumn column columns ty) => Alias column -> Expression tables (Grouped bys) params ty Source #

getGroup2 :: (HasTable table tables columns, HasColumn column columns ty) => Alias table -> Alias column -> Expression tables (Grouped bys) params ty Source #

Instances

(KnownSymbol table, KnownSymbol column, GroupedBy table column bys) => GroupedBy table column ((:) (Symbol, Symbol) tabcol bys) Source # 

Methods

getGroup1 :: (HasUnique ColumnsType table tables columns, HasColumn column columns ty) => Alias column -> Expression tables (Grouped (((Symbol, Symbol) ': tabcol) bys)) params ty Source #

getGroup2 :: (HasTable table tables columns, HasColumn column columns ty) => Alias table -> Alias column -> Expression tables (Grouped (((Symbol, Symbol) ': tabcol) bys)) params ty Source #

(KnownSymbol table, KnownSymbol column) => GroupedBy table column ((:) (Symbol, Symbol) ((,) Symbol Symbol table column) bys) Source # 

Methods

getGroup1 :: (HasUnique ColumnsType table tables columns, HasColumn column columns ty) => Alias column -> Expression tables (Grouped (((Symbol, Symbol) ': (Symbol, Symbol) table column) bys)) params ty Source #

getGroup2 :: (HasTable table tables columns, HasColumn column columns ty) => Alias table -> Alias column -> Expression tables (Grouped (((Symbol, Symbol) ': (Symbol, Symbol) table column) bys)) params ty Source #

Default

def :: Expression '[] Ungrouped params (Optional (nullity ty)) Source #

>>> renderExpression def
"DEFAULT"

unDef Source #

Arguments

:: Expression '[] Ungrouped params (Required (nullity ty))

not DEFAULT

-> Expression '[] Ungrouped params (Optional (nullity ty)) 
>>> renderExpression $ unDef false
"FALSE"

Null

null_ :: Expression tables grouping params (optionality (Null ty)) Source #

analagous to Nothing

>>> renderExpression $ null_
"NULL"

unNull Source #

Arguments

:: Expression tables grouping params (optionality (NotNull ty))

not NULL

-> Expression tables grouping params (optionality (Null ty)) 

analagous to Just

>>> renderExpression $ unNull true
"TRUE"

coalesce Source #

Arguments

:: [Expression tables grouping params (Required (Null ty))]

NULLs may be present

-> Expression tables grouping params (Required (NotNull ty))

NULL is absent

-> Expression tables grouping params (Required (NotNull ty)) 

return the leftmost value which is not NULL

>>> renderExpression $ coalesce [null_, unNull true] false
"COALESCE(NULL, TRUE, FALSE)"

fromNull Source #

Arguments

:: Expression tables grouping params (Required (NotNull ty))

what to convert NULL to

-> Expression tables grouping params (Required (Null ty)) 
-> Expression tables grouping params (Required (NotNull ty)) 

analagous to fromMaybe using COALESCE

>>> renderExpression $ fromNull true null_
"COALESCE(NULL, TRUE)"

isNull Source #

Arguments

:: Expression tables grouping params (Required (Null ty))

possibly NULL

-> Condition tables grouping params 
>>> renderExpression $ null_ & isNull
"NULL IS NULL"

isn'tNull Source #

Arguments

:: Expression tables grouping params (Required (Null ty))

possibly NULL

-> Condition tables grouping params 
>>> renderExpression $ null_ & isn'tNull
"NULL IS NOT NULL"

matchNull Source #

Arguments

:: Expression tables grouping params (Required nullty)

what to convert NULL to

-> (Expression tables grouping params (Required (NotNull ty)) -> Expression tables grouping params (Required nullty))

function to perform when NULL is absent

-> Expression tables grouping params (Required (Null ty)) 
-> Expression tables grouping params (Required nullty) 

analagous to maybe using IS NULL

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

nullIf Source #

Arguments

:: Expression tables grouping params (Required (NotNull ty))

NULL is absent

-> Expression tables grouping params (Required (NotNull ty))

NULL is absent

-> Expression tables grouping params (Required (Null ty)) 

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

>>> :set -XTypeApplications -XDataKinds
>>> renderExpression @_ @_ @'[_] $ fromNull false (nullIf false (param @1))
"COALESCE(NULL IF (FALSE, ($1 :: bool)), FALSE)"

Functions

unsafeBinaryOp Source #

Arguments

:: ByteString

operator

-> Expression tables grouping params (Required ty0) 
-> Expression tables grouping params (Required ty1) 
-> Expression tables grouping params (Required ty2) 
>>> renderExpression $ unsafeBinaryOp "OR" true false
"(TRUE OR FALSE)"

unsafeUnaryOp Source #

Arguments

:: ByteString

operator

-> Expression tables grouping params (Required ty0) 
-> Expression tables grouping params (Required ty1) 
>>> renderExpression $ unsafeUnaryOp "NOT" true
"(NOT TRUE)"

unsafeFunction Source #

Arguments

:: ByteString

function

-> Expression tables grouping params (Required xty) 
-> Expression tables grouping params (Required yty) 
>>> renderExpression $ unsafeFunction "f" true
"f(TRUE)"

atan2_ Source #

Arguments

:: PGFloating float 
=> Expression tables grouping params (Required (nullity float))

numerator

-> Expression tables grouping params (Required (nullity float))

denominator

-> Expression tables grouping params (Required (nullity float)) 
>>> renderExpression @_ @_ @_ @(_ (_ 'PGfloat4)) $ atan2_ pi 2
"atan2(pi(), 2)"

cast Source #

Arguments

:: TypeExpression (Required (Null ty1))

type to cast as

-> Expression tables grouping params (Required (nullity ty0))

value to convert

-> Expression tables grouping params (Required (nullity ty1)) 
>>> renderExpression $ true & cast int4
"(TRUE :: int4)"

quot_ Source #

Arguments

:: PGIntegral int 
=> Expression tables grouping params (Required (nullity int))

numerator

-> Expression tables grouping params (Required (nullity int))

denominator

-> Expression tables grouping params (Required (nullity int)) 

integer division, truncates the result

>>> renderExpression @_ @_ @_ @(_(_ 'PGint2)) $ 5 `quot_` 2
"(5 / 2)"

rem_ Source #

Arguments

:: PGIntegral int 
=> Expression tables grouping params (Required (nullity int))

numerator

-> Expression tables grouping params (Required (nullity int))

denominator

-> Expression tables grouping params (Required (nullity int)) 

remainder upon integer division

>>> renderExpression @_ @_ @_ @(_ (_ 'PGint2)) $ 5 `rem_` 2
"(5 % 2)"

trunc Source #

Arguments

:: PGFloating frac 
=> Expression tables grouping params (Required (nullity frac))

fractional number

-> Expression tables grouping params (Required (nullity frac)) 
>>> renderExpression @_ @_ @_ @(_ (_ 'PGfloat4)) $ trunc pi
"trunc(pi())"

round_ Source #

Arguments

:: PGFloating frac 
=> Expression tables grouping params (Required (nullity frac))

fractional number

-> Expression tables grouping params (Required (nullity frac)) 
>>> renderExpression @_ @_ @_ @(_ (_ 'PGfloat4)) $ round_ pi
"round(pi())"

ceiling_ Source #

Arguments

:: PGFloating frac 
=> Expression tables grouping params (Required (nullity frac))

fractional number

-> Expression tables grouping params (Required (nullity frac)) 
>>> renderExpression @_ @_ @_ @(_ (_ 'PGfloat4)) $ ceiling_ pi
"ceiling(pi())"

greatest Source #

Arguments

:: Expression tables grouping params (Required nullty)

needs at least 1 argument

-> [Expression tables grouping params (Required nullty)]

or more

-> Expression tables grouping params (Required nullty) 
>>> renderExpression @_ @_ @'[_] $ greatest currentTimestamp [param @1]
"GREATEST(CURRENT_TIMESTAMP, ($1 :: timestamp with time zone))"

least Source #

Arguments

:: Expression tables grouping params (Required nullty)

needs at least 1 argument

-> [Expression tables grouping params (Required nullty)]

or more

-> Expression tables grouping params (Required nullty) 
>>> renderExpression $ least currentTimestamp [null_]
"LEAST(CURRENT_TIMESTAMP, NULL)"

Conditions

type Condition tables grouping params = Expression tables grouping params (Required (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 tables grouping params Source #

>>> renderExpression true
"TRUE"

false :: Condition tables grouping params Source #

>>> renderExpression false
"FALSE"

not_ :: Condition tables grouping params -> Condition tables grouping params Source #

>>> renderExpression $ not_ true
"(NOT TRUE)"

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

>>> renderExpression $ true .&& false
"(TRUE AND FALSE)"

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

>>> renderExpression $ true .|| false
"(TRUE OR FALSE)"

caseWhenThenElse :: [(Condition tables grouping params, Expression tables grouping params (Required ty))] -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty) Source #

>>> renderExpression @_ @_ @_ @(_ (_ 'PGint2)) $ caseWhenThenElse [(true, 1), (false, 2)] 3
"CASE WHEN TRUE THEN 1 WHEN FALSE THEN 2 ELSE 3 END"

ifThenElse :: Condition tables grouping params -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty) Source #

>>> renderExpression @_ @_ @_ @(_ (_ 'PGint2)) $ ifThenElse true 1 0
"CASE WHEN TRUE THEN 1 ELSE 0 END"

(.==) infix 4 Source #

Arguments

:: Expression tables grouping params (Required (nullity ty))

lhs

-> Expression tables grouping params (Required (nullity ty))

rhs

-> Expression tables grouping params (Required (nullity PGbool)) 

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

>>> renderExpression $ unNull true .== null_
"(TRUE = NULL)"

(./=) infix 4 Source #

Arguments

:: Expression tables grouping params (Required (nullity ty))

lhs

-> Expression tables grouping params (Required (nullity ty))

rhs

-> Expression tables grouping params (Required (nullity PGbool)) 
>>> renderExpression $ unNull true ./= null_
"(TRUE <> NULL)"

(.>=) infix 4 Source #

Arguments

:: Expression tables grouping params (Required (nullity ty))

lhs

-> Expression tables grouping params (Required (nullity ty))

rhs

-> Expression tables grouping params (Required (nullity PGbool)) 
>>> renderExpression $ unNull true .>= null_
"(TRUE >= NULL)"

(.<) infix 4 Source #

Arguments

:: Expression tables grouping params (Required (nullity ty))

lhs

-> Expression tables grouping params (Required (nullity ty))

rhs

-> Expression tables grouping params (Required (nullity PGbool)) 
>>> renderExpression $ unNull true .< null_
"(TRUE < NULL)"

(.<=) infix 4 Source #

Arguments

:: Expression tables grouping params (Required (nullity ty))

lhs

-> Expression tables grouping params (Required (nullity ty))

rhs

-> Expression tables grouping params (Required (nullity PGbool)) 
>>> renderExpression $ unNull true .<= null_
"(TRUE <= NULL)"

(.>) infix 4 Source #

Arguments

:: Expression tables grouping params (Required (nullity ty))

lhs

-> Expression tables grouping params (Required (nullity ty))

rhs

-> Expression tables grouping params (Required (nullity PGbool)) 
>>> renderExpression $ unNull true .> null_
"(TRUE > NULL)"

Time

currentDate :: Expression tables grouping params (Required (nullity PGdate)) Source #

>>> renderExpression $ currentDate
"CURRENT_DATE"

currentTime :: Expression tables grouping params (Required (nullity PGtimetz)) Source #

>>> renderExpression $ currentTime
"CURRENT_TIME"

currentTimestamp :: Expression tables grouping params (Required (nullity PGtimestamptz)) Source #

>>> renderExpression $ currentTimestamp
"CURRENT_TIMESTAMP"

localTime :: Expression tables grouping params (Required (nullity PGtime)) Source #

>>> renderExpression $ localTime
"LOCALTIME"

localTimestamp :: Expression tables grouping params (Required (nullity PGtimestamp)) Source #

>>> renderExpression $ localTimestamp
"LOCALTIMESTAMP"

Text

lower Source #

Arguments

:: Expression tables grouping params (Required (nullity PGtext))

string to lower case

-> Expression tables grouping params (Required (nullity PGtext)) 
>>> renderExpression $ lower "ARRRGGG"
"lower(E'ARRRGGG')"

upper Source #

Arguments

:: Expression tables grouping params (Required (nullity PGtext))

string to upper case

-> Expression tables grouping params (Required (nullity PGtext)) 
>>> renderExpression $ upper "eeee"
"upper(E'eeee')"

charLength Source #

Arguments

:: Expression tables grouping params (Required (nullity PGtext))

string to measure

-> Expression tables grouping params (Required (nullity PGint4)) 
>>> renderExpression $ charLength "four"
"char_length(E'four')"

like Source #

Arguments

:: Expression tables grouping params (Required (nullity PGtext))

string

-> Expression tables grouping params (Required (nullity PGtext))

pattern

-> Expression tables grouping params (Required (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.

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

Aggregation

unsafeAggregate Source #

Arguments

:: ByteString

aggregate function

-> Expression tables Ungrouped params (Required xty) 
-> Expression tables (Grouped bys) params (Required yty) 

escape hatch to define aggregate functions

unsafeAggregateDistinct Source #

Arguments

:: ByteString

aggregate function

-> Expression tables Ungrouped params (Required xty) 
-> Expression tables (Grouped bys) params (Required yty) 

escape hatch to define aggregate functions over distinct values

sum_ Source #

Arguments

:: PGNum ty 
=> Expression tables Ungrouped params (Required (nullity ty))

what to sum

-> Expression tables (Grouped bys) params (Required (nullity ty)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGnumeric)]] $ sum_ #col
"sum(col)"

sumDistinct Source #

Arguments

:: PGNum ty 
=> Expression tables Ungrouped params (Required (nullity ty))

what to sum

-> Expression tables (Grouped bys) params (Required (nullity ty)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGnumeric)]] $ sumDistinct #col
"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,avgDistinct Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity ty))

what to average

-> Expression tables (Grouped bys) params (Required (nullity avg)) 

Instances

PGAvg PGType PGint2 PGnumeric Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGint4 PGnumeric Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGint8 PGnumeric Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGnumeric PGnumeric Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGnumeric)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGfloat4 PGfloat8 Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGfloat8)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGfloat8)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGfloat8 PGfloat8 Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGfloat8)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGfloat8)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

PGAvg PGType PGinterval PGinterval Source # 

Methods

avg :: Expression tables Ungrouped params (Required (nullity PGinterval)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

avgDistinct :: Expression tables Ungrouped params (Required (nullity PGinterval)) -> Expression tables (Grouped bys) params (Required (nullity avg)) Source #

bitAnd Source #

Arguments

:: PGIntegral int 
=> Expression tables Ungrouped params (Required (nullity int))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity int)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGint4)]] $ bitAnd #col
"bit_and(col)"

bitOr Source #

Arguments

:: PGIntegral int 
=> Expression tables Ungrouped params (Required (nullity int))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity int)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGint4)]] $ bitOr #col
"bit_or(col)"

boolAnd Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity PGbool))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity PGbool)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ boolAnd #col
"bool_and(col)"

boolOr Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity PGbool))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity PGbool)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ boolOr #col
"bool_or(col)"

bitAndDistinct Source #

Arguments

:: PGIntegral int 
=> Expression tables Ungrouped params (Required (nullity int))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity int)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGint4)]] $ bitAndDistinct #col
"bit_and(DISTINCT col)"

bitOrDistinct Source #

Arguments

:: PGIntegral int 
=> Expression tables Ungrouped params (Required (nullity int))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity int)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGint4)]] $ bitOrDistinct #col
"bit_or(DISTINCT col)"

boolAndDistinct Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity PGbool))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity PGbool)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ boolAndDistinct #col
"bool_and(DISTINCT col)"

boolOrDistinct Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity PGbool))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity PGbool)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ boolOrDistinct #col
"bool_or(DISTINCT col)"

countStar :: Expression tables (Grouped bys) params (Required (NotNull PGint8)) Source #

A special aggregation that does not require an input

>>> renderExpression countStar
"count(*)"

count Source #

Arguments

:: Expression tables Ungrouped params (Required ty)

what to count

-> Expression tables (Grouped bys) params (Required (NotNull PGint8)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Optional _]] $ count #col
"count(col)"

countDistinct Source #

Arguments

:: Expression tables Ungrouped params (Required ty)

what to count

-> Expression tables (Grouped bys) params (Required (NotNull PGint8)) 
>>> renderExpression @'[_ ::: '["col" ::: 'Required _]] $ countDistinct #col
"count(DISTINCT col)"

every Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity PGbool))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity PGbool)) 

synonym for boolAnd

>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ every #col
"every(col)"

everyDistinct Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity PGbool))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity PGbool)) 

synonym for boolAndDistinct

>>> renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ everyDistinct #col
"every(DISTINCT col)"

max_ Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity ty))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity ty)) 

minimum and maximum aggregation

maxDistinct Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity ty))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity ty)) 

minimum and maximum aggregation

min_ Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity ty))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity ty)) 

minimum and maximum aggregation

minDistinct Source #

Arguments

:: Expression tables Ungrouped params (Required (nullity ty))

what to aggregate

-> Expression tables (Grouped bys) params (Required (nullity ty)) 

minimum and maximum aggregation

Tables

newtype Table (schema :: TablesType) (columns :: ColumnsType) Source #

A Table from a schema without its alias with an IsLabel instance to call a table reference by its alias.

Constructors

UnsafeTable 

Instances

HasTable table schema columns => IsLabel table (Table schema columns) Source # 

Methods

fromLabel :: Table schema columns #

Eq (Table schema columns) Source # 

Methods

(==) :: Table schema columns -> Table schema columns -> Bool #

(/=) :: Table schema columns -> Table schema columns -> Bool #

Ord (Table schema columns) Source # 

Methods

compare :: Table schema columns -> Table schema columns -> Ordering #

(<) :: Table schema columns -> Table schema columns -> Bool #

(<=) :: Table schema columns -> Table schema columns -> Bool #

(>) :: Table schema columns -> Table schema columns -> Bool #

(>=) :: Table schema columns -> Table schema columns -> Bool #

max :: Table schema columns -> Table schema columns -> Table schema columns #

min :: Table schema columns -> Table schema columns -> Table schema columns #

Show (Table schema columns) Source # 

Methods

showsPrec :: Int -> Table schema columns -> ShowS #

show :: Table schema columns -> String #

showList :: [Table schema columns] -> ShowS #

Generic (Table schema columns) Source # 

Associated Types

type Rep (Table schema columns) :: * -> * #

Methods

from :: Table schema columns -> Rep (Table schema columns) x #

to :: Rep (Table schema columns) x -> Table schema columns #

NFData (Table schema columns) Source # 

Methods

rnf :: Table schema columns -> () #

type Rep (Table schema columns) Source # 
type Rep (Table schema columns) = D1 * (MetaData "Table" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.1.1.4-k5IDJoGvjq2Crr3wWyEON" True) (C1 * (MetaCons "UnsafeTable" PrefixI True) (S1 * (MetaSel (Just Symbol "renderTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

class KnownSymbol table => HasTable table tables columns | table tables -> columns where Source #

A HasTable constraint indicates a table reference.

Methods

getTable :: Alias table -> Table tables columns Source #

Instances

(KnownSymbol table, HasTable table schema columns) => HasTable table ((:) (Symbol, ColumnsType) table' schema) columns Source # 

Methods

getTable :: Alias table -> Table (((Symbol, ColumnsType) ': table') schema) columns Source #

KnownSymbol table => HasTable table ((:) (Symbol, ColumnsType) ((:::) ColumnsType table columns) tables) columns Source # 

Methods

getTable :: Alias table -> Table (((Symbol, ColumnsType) ': (ColumnsType ::: table) columns) tables) columns Source #

TypeExpression

newtype TypeExpression (ty :: ColumnType) Source #

TypeExpressions are used in casts and createTable commands.

Instances

Eq (TypeExpression ty) Source # 
Ord (TypeExpression ty) Source # 
Show (TypeExpression ty) Source # 
Generic (TypeExpression ty) Source # 

Associated Types

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

Methods

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

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

NFData (TypeExpression ty) Source # 

Methods

rnf :: TypeExpression ty -> () #

type Rep (TypeExpression ty) Source # 
type Rep (TypeExpression ty) = D1 * (MetaData "TypeExpression" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.1.1.4-k5IDJoGvjq2Crr3wWyEON" True) (C1 * (MetaCons "UnsafeTypeExpression" PrefixI True) (S1 * (MetaSel (Just Symbol "renderTypeExpression") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

class PGTyped (ty :: PGType) where Source #

pgtype is a demoted version of a PGType

Minimal complete definition

pgtype

Instances

PGTyped PGbool Source # 
PGTyped PGint2 Source # 
PGTyped PGint4 Source # 
PGTyped PGint8 Source # 
PGTyped PGnumeric Source # 
PGTyped PGfloat4 Source # 
PGTyped PGfloat8 Source # 
PGTyped PGtext Source # 
PGTyped PGbytea Source # 
PGTyped PGtimestamp Source # 
PGTyped PGtimestamptz Source # 
PGTyped PGdate Source # 
PGTyped PGtime Source # 
PGTyped PGtimetz Source # 
PGTyped PGinterval Source # 
PGTyped PGuuid Source # 
PGTyped PGjson Source # 
PGTyped PGjsonb Source # 
(KnownNat n, (<=) 1 n) => PGTyped (PGchar n) Source # 
(KnownNat n, (<=) 1 n) => PGTyped (PGvarchar n) Source # 

bool :: TypeExpression (Required (Null PGbool)) Source #

logical Boolean (true/false)

int2 :: TypeExpression (Required (Null PGint2)) Source #

signed two-byte integer

smallint :: TypeExpression (Required (Null PGint2)) Source #

signed two-byte integer

int4 :: TypeExpression (Required (Null PGint4)) Source #

signed four-byte integer

int :: TypeExpression (Required (Null PGint4)) Source #

signed four-byte integer

integer :: TypeExpression (Required (Null PGint4)) Source #

signed four-byte integer

int8 :: TypeExpression (Required (Null PGint8)) Source #

signed eight-byte integer

bigint :: TypeExpression (Required (Null PGint8)) Source #

signed eight-byte integer

numeric :: TypeExpression (Required (Null PGnumeric)) Source #

arbitrary precision numeric type

float4 :: TypeExpression (Required (Null PGfloat4)) Source #

single precision floating-point number (4 bytes)

real :: TypeExpression (Required (Null PGfloat4)) Source #

single precision floating-point number (4 bytes)

float8 :: TypeExpression (Required (Null PGfloat8)) Source #

double precision floating-point number (8 bytes)

doublePrecision :: TypeExpression (Required (Null PGfloat8)) Source #

double precision floating-point number (8 bytes)

serial2 :: TypeExpression (Optional (NotNull PGint2)) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type `PGint2

smallserial :: TypeExpression (Optional (NotNull PGint2)) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type `PGint2

serial4 :: TypeExpression (Optional (NotNull PGint4)) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type `PGint4

serial :: TypeExpression (Optional (NotNull PGint4)) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type `PGint4

serial8 :: TypeExpression (Optional (NotNull PGint8)) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type `PGint8

bigserial :: TypeExpression (Optional (NotNull PGint8)) Source #

not a true type, but merely a notational convenience for creating unique identifier columns with type `PGint8

text :: TypeExpression (Required (Null PGtext)) Source #

variable-length character string

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

fixed-length character string

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

fixed-length character string

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

variable-length character string

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

variable-length character string

bytea :: TypeExpression (Required (Null PGbytea)) Source #

binary data ("byte array")

timestamp :: TypeExpression (Required (Null PGtimestamp)) Source #

date and time (no time zone)

timestampWithTimeZone :: TypeExpression (Required (Null PGtimestamptz)) Source #

date and time, including time zone

date :: TypeExpression (Required (Null PGdate)) Source #

calendar date (year, month, day)

time :: TypeExpression (Required (Null PGtime)) Source #

time of day (no time zone)

timeWithTimeZone :: TypeExpression (Required (Null PGtimetz)) Source #

time of day, including time zone

uuid :: TypeExpression (Required (Null PGuuid)) Source #

universally unique identifier

inet :: TypeExpression (Required (Null PGinet)) Source #

IPv4 or IPv6 host address

json :: TypeExpression (Required (Null PGjson)) Source #

textual JSON data

jsonb :: TypeExpression (Required (Null PGjsonb)) Source #

binary JSON data, decomposed

notNull :: TypeExpression (optionality (Null ty)) -> TypeExpression (optionality (NotNull ty)) Source #

used in createTable commands as a column constraint to ensure NULL is not present

default_ :: Expression '[] Ungrouped '[] (Required ty) -> TypeExpression (Required ty) -> TypeExpression (Optional ty) Source #

used in createTable commands as a column constraint to give a default

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 $.

Since: 4.8.0.0

data NP k (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 k a ([] k) 
(:*) :: NP k a ((:) k x xs) infixr 5 

Instances

HTrans k1 [k1] k2 [k2] (NP k1) (NP k2) 

Methods

htrans :: AllZipN (NP k1) (NP k2) (NP k1) k2 (NP k2) l2 (Prod (NP k1) (NP k2) h1) c xs ys => proxy c -> (forall (x :: NP k1) (y :: k2). c x y => f x -> g y) -> h1 f xs -> h2 g ys #

hcoerce :: (AllZipN (NP k1) (NP k2) (NP k1) k2 (NP k2) l2 (Prod (NP k1) (NP k2) h1) (LiftedCoercible * (NP k1) k2 f g) xs ys, HTrans (NP k1) (NP k2) k2 l2 h1 h2) => h1 f xs -> h2 g ys #

HPure k [k] (NP k) 

Methods

hpure :: SListIN (NP k) l h xs => (forall (a :: NP k). f a) -> h f xs #

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

HAp k [k] (NP k) 

Methods

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

HCollapse k [k] (NP k) 

Methods

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

HSequence k [k] (NP k) 

Methods

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

All k (Compose * k Eq f) xs => Eq (NP k f xs) 

Methods

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

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

(All k (Compose * k Eq f) xs, All k (Compose * k Ord f) xs) => Ord (NP k f xs) 

Methods

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

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

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

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

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

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

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

All k (Compose * k Show f) xs => Show (NP k f xs) 

Methods

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

show :: NP k f xs -> String #

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

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

Since: 0.2.5.0

Methods

rnf :: NP k f xs -> () #

type AllZipN k [k] a b [a] [b] (NP k) c 
type AllZipN k [k] a b [a] [b] (NP k) c = AllZip a b c
type Same k1 [k1] k2 [k2] (NP k1) 
type Same k1 [k1] k2 [k2] (NP k1) = NP k2
type Prod k [k] (NP k) 
type Prod k [k] (NP k) = NP k
type UnProd k [k] (NP k) 
type UnProd k [k] (NP k) = NS k
type SListIN k [k] (NP k) 
type SListIN k [k] (NP k) = SListI k
type CollapseTo k [k] (NP k) a 
type CollapseTo k [k] (NP k) a = [a]
type AllN k [k] (NP k) c 
type AllN k [k] (NP k) c = All k c