squeal-postgresql-0.2.1.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 (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 [(Symbol, NullityType)] relation relations columns, Has NullityType column columns ty, GroupedBy [(Symbol, Symbol)] relation column bys) => IsQualified relation column (Expression relations (Grouped bys) params ty) Source # 

Methods

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

(Has [(Symbol, NullityType)] relation relations columns, Has NullityType column columns ty) => IsQualified relation column (Expression relations Ungrouped params ty) Source # 

Methods

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

(HasUnique [(Symbol, NullityType)] relation relations columns, Has NullityType column columns ty, GroupedBy [(Symbol, Symbol)] relation column bys) => IsLabel column (Expression relations (Grouped bys) params ty) Source # 

Methods

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

(HasUnique [(Symbol, NullityType)] relation relations columns, Has NullityType column columns ty) => IsLabel column (Expression relations Ungrouped params ty) Source # 

Methods

fromLabel :: Expression relations Ungrouped params ty #

Eq (Expression relations grouping params ty) Source # 

Methods

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

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

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

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Methods

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

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

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

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

Methods

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

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

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

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

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

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

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

Ord (Expression relations grouping params ty) Source # 

Methods

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

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

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

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

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

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

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

Show (Expression relations grouping params ty) Source # 

Methods

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

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

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

IsString (Expression relations grouping params (nullity PGtext)) Source # 

Methods

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

Generic (Expression relations grouping params ty) Source # 

Associated Types

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

Methods

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

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

Monoid (Expression relations grouping params (nullity PGtext)) Source # 

Methods

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

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

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

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

Methods

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

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

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

NFData (Expression relations grouping params ty) Source # 

Methods

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

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

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

param :: Expression relations grouping params ty Source #

Instances

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

Methods

param :: Expression relations grouping ((NullityType ': ty') params) ty Source #

PGTyped (PGTypeOf ty1) => HasParameter 1 ((:) NullityType ty1 tys) ty1 Source # 

Methods

param :: Expression relations grouping ((NullityType ': ty1) tys) ty1 Source #

Null

null_ :: Expression relations grouping params (Null ty) Source #

analagous to Nothing

>>> renderExpression $ null_
"NULL"

unNull Source #

Arguments

:: Expression relations grouping params (NotNull ty)

not NULL

-> Expression relations grouping params (Null ty) 

analagous to Just

>>> renderExpression $ unNull true
"TRUE"

coalesce Source #

Arguments

:: [Expression relations grouping params (Null ty)]

NULLs may be present

-> Expression relations grouping params (NotNull ty)

NULL is absent

-> Expression relations grouping params (NotNull ty) 

return the leftmost value which is not NULL

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

fromNull Source #

Arguments

:: Expression relations grouping params (NotNull ty)

what to convert NULL to

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

analagous to fromMaybe using COALESCE

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

isNull Source #

Arguments

:: Expression relations grouping params (Null ty)

possibly NULL

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

isn'tNull Source #

Arguments

:: Expression relations grouping params (Null ty)

possibly NULL

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

matchNull Source #

Arguments

:: Expression relations grouping params nullty

what to convert NULL to

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

function to perform when NULL is absent

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

NULL is absent

-> Expression relations grouping params (NotNull ty)

NULL is absent

-> Expression relations grouping params (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)"

Arrays

array Source #

Arguments

:: [Expression relations grouping params (Null ty)]

array elements

-> Expression relations grouping params (nullity (PGvararray ty)) 
>>> renderExpression $ array [null_, unNull false, unNull true]
"ARRAY[NULL, FALSE, TRUE]"

Functions

unsafeBinaryOp Source #

Arguments

:: ByteString

operator

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

unsafeUnaryOp Source #

Arguments

:: ByteString

operator

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

unsafeFunction Source #

Arguments

:: ByteString

function

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

atan2_ Source #

Arguments

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

numerator

-> Expression relations grouping params (nullity float)

denominator

-> Expression relations grouping params (nullity float) 
>>> :{
let
  expression :: Expression relations grouping params (nullity 'PGfloat4)
  expression = atan2_ pi 2
in renderExpression expression
:}
"atan2(pi(), 2)"

cast Source #

Arguments

:: TypeExpression (NoDef :=> Null ty1)

type to cast as

-> Expression relations grouping params (nullity ty0)

value to convert

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

quot_ Source #

Arguments

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

numerator

-> Expression relations grouping params (nullity int)

denominator

-> Expression relations grouping params (nullity int) 

integer division, truncates the result

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

rem_ Source #

Arguments

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

numerator

-> Expression relations grouping params (nullity int)

denominator

-> Expression relations grouping params (nullity int) 

remainder upon integer division

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

trunc Source #

Arguments

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

fractional number

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

round_ Source #

Arguments

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

fractional number

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

ceiling_ Source #

Arguments

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

fractional number

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

greatest Source #

Arguments

:: Expression relations grouping params nullty

needs at least 1 argument

-> [Expression relations grouping params nullty]

or more

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

least Source #

Arguments

:: Expression relations grouping params nullty

needs at least 1 argument

-> [Expression relations grouping params nullty]

or more

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

Conditions

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

>>> renderExpression true
"TRUE"

false :: Condition relations grouping params Source #

>>> renderExpression false
"FALSE"

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

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

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

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

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

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

caseWhenThenElse Source #

Arguments

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

whens and thens

-> Expression relations grouping params ty

else

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

ifThenElse Source #

Arguments

:: Condition relations grouping params 
-> Expression relations grouping params ty

then

-> Expression relations grouping params ty

else

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

(.==) infix 4 Source #

Arguments

:: Expression relations grouping params (nullity ty)

lhs

-> Expression relations grouping params (nullity ty)

rhs

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

lhs

-> Expression relations grouping params (nullity ty)

rhs

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

(.>=) infix 4 Source #

Arguments

:: Expression relations grouping params (nullity ty)

lhs

-> Expression relations grouping params (nullity ty)

rhs

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

(.<) infix 4 Source #

Arguments

:: Expression relations grouping params (nullity ty)

lhs

-> Expression relations grouping params (nullity ty)

rhs

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

(.<=) infix 4 Source #

Arguments

:: Expression relations grouping params (nullity ty)

lhs

-> Expression relations grouping params (nullity ty)

rhs

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

(.>) infix 4 Source #

Arguments

:: Expression relations grouping params (nullity ty)

lhs

-> Expression relations grouping params (nullity ty)

rhs

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

Time

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

>>> renderExpression currentDate
"CURRENT_DATE"

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

>>> renderExpression currentTime
"CURRENT_TIME"

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

>>> renderExpression currentTimestamp
"CURRENT_TIMESTAMP"

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

>>> renderExpression localTime
"LOCALTIME"

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

>>> renderExpression localTimestamp
"LOCALTIMESTAMP"

Text

lower Source #

Arguments

:: Expression relations grouping params (nullity PGtext)

string to lower case

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

upper Source #

Arguments

:: Expression relations grouping params (nullity PGtext)

string to upper case

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

charLength Source #

Arguments

:: Expression relations grouping params (nullity PGtext)

string to measure

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

like Source #

Arguments

:: Expression relations grouping params (nullity PGtext)

string

-> Expression relations grouping params (nullity PGtext)

pattern

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

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

Aggregation

unsafeAggregate Source #

Arguments

:: ByteString

aggregate function

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

escape hatch to define aggregate functions

unsafeAggregateDistinct Source #

Arguments

:: ByteString

aggregate function

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

escape hatch to define aggregate functions over distinct values

sum_ Source #

Arguments

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

what to sum

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

sumDistinct Source #

Arguments

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

what to sum

-> Expression relations (Grouped bys) params (nullity ty) 
>>> :{
let
  expression :: Expression '[tab ::: '["col" ::: nullity 'PGnumeric]] ('Grouped bys) params (nullity 'PGnumeric)
  expression = sumDistinct #col
in renderExpression 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,avgDistinct Source #

Arguments

:: Expression relations Ungrouped params (nullity ty)

what to average

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

Instances

PGAvg PGType PGint2 PGnumeric Source # 

Methods

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

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

PGAvg PGType PGint4 PGnumeric Source # 

Methods

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

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

PGAvg PGType PGint8 PGnumeric Source # 

Methods

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

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

PGAvg PGType PGnumeric PGnumeric Source # 

Methods

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

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

PGAvg PGType PGfloat4 PGfloat8 Source # 

Methods

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

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

PGAvg PGType PGfloat8 PGfloat8 Source # 

Methods

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

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

PGAvg PGType PGinterval PGinterval Source # 

Methods

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

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

bitAnd Source #

Arguments

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

what to aggregate

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

bitOr Source #

Arguments

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

what to aggregate

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

boolAnd Source #

Arguments

:: Expression relations Ungrouped params (nullity PGbool)

what to aggregate

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

boolOr Source #

Arguments

:: Expression relations Ungrouped params (nullity PGbool)

what to aggregate

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

bitAndDistinct Source #

Arguments

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

what to aggregate

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

bitOrDistinct Source #

Arguments

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

what to aggregate

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

boolAndDistinct Source #

Arguments

:: Expression relations Ungrouped params (nullity PGbool)

what to aggregate

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

boolOrDistinct Source #

Arguments

:: Expression relations Ungrouped params (nullity PGbool)

what to aggregate

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

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

A special aggregation that does not require an input

>>> renderExpression countStar
"count(*)"

count Source #

Arguments

:: Expression relations Ungrouped params ty

what to count

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

countDistinct Source #

Arguments

:: Expression relations Ungrouped params ty

what to count

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

every Source #

Arguments

:: Expression relations Ungrouped params (nullity PGbool)

what to aggregate

-> Expression relations (Grouped bys) params (nullity PGbool) 

synonym for boolAnd

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

everyDistinct Source #

Arguments

:: Expression relations Ungrouped params (nullity PGbool)

what to aggregate

-> Expression relations (Grouped bys) params (nullity PGbool) 

synonym for boolAndDistinct

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

max_ Source #

Arguments

:: Expression relations Ungrouped params (nullity ty)

what to aggregate

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

minimum and maximum aggregation

maxDistinct Source #

Arguments

:: Expression relations Ungrouped params (nullity ty)

what to aggregate

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

minimum and maximum aggregation

min_ Source #

Arguments

:: Expression relations Ungrouped params (nullity ty)

what to aggregate

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

minimum and maximum aggregation

minDistinct Source #

Arguments

:: Expression relations Ungrouped params (nullity ty)

what to aggregate

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

minimum and maximum aggregation

Tables

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

A Table from a table expression is a way to call a table reference by its alias.

Constructors

UnsafeTable 

Instances

(Has TableType alias schema table, (~) RelationType relation (ColumnsToRelation (TableToColumns table))) => IsLabel alias (Table schema relation) Source # 

Methods

fromLabel :: Table schema relation #

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.2.1.0-LBCcz8qiN2YKV8JaWeUPNP" True) (C1 * (MetaCons "UnsafeTable" PrefixI True) (S1 * (MetaSel (Just Symbol "renderTable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ByteString)))

Types

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.2.1.0-LBCcz8qiN2YKV8JaWeUPNP" 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 # 
PGTyped ty => PGTyped (PGvararray ty) Source # 
(KnownNat n, PGTyped ty) => PGTyped (PGfixarray n ty) Source # 

bool :: TypeExpression (NoDef :=> Null PGbool) Source #

logical Boolean (true/false)

int2 :: TypeExpression (NoDef :=> Null PGint2) Source #

signed two-byte integer

smallint :: TypeExpression (NoDef :=> Null PGint2) Source #

signed two-byte integer

int4 :: TypeExpression (NoDef :=> Null PGint4) Source #

signed four-byte integer

int :: TypeExpression (NoDef :=> Null PGint4) Source #

signed four-byte integer

integer :: TypeExpression (NoDef :=> Null PGint4) Source #

signed four-byte integer

int8 :: TypeExpression (NoDef :=> Null PGint8) Source #

signed eight-byte integer

bigint :: TypeExpression (NoDef :=> Null PGint8) Source #

signed eight-byte integer

numeric :: TypeExpression (NoDef :=> Null PGnumeric) Source #

arbitrary precision numeric type

float4 :: TypeExpression (NoDef :=> Null PGfloat4) Source #

single precision floating-point number (4 bytes)

real :: TypeExpression (NoDef :=> Null PGfloat4) Source #

single precision floating-point number (4 bytes)

float8 :: TypeExpression (NoDef :=> Null PGfloat8) Source #

double precision floating-point number (8 bytes)

doublePrecision :: TypeExpression (NoDef :=> Null PGfloat8) Source #

double precision floating-point number (8 bytes)

serial2 :: TypeExpression (Def :=> NotNull PGint2) Source #

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

smallserial :: TypeExpression (Def :=> NotNull PGint2) Source #

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

serial4 :: TypeExpression (Def :=> NotNull PGint4) Source #

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

serial :: TypeExpression (Def :=> NotNull PGint4) Source #

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

serial8 :: TypeExpression (Def :=> NotNull PGint8) Source #

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

bigserial :: TypeExpression (Def :=> NotNull PGint8) Source #

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

text :: TypeExpression (NoDef :=> Null PGtext) Source #

variable-length character string

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

fixed-length character string

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

fixed-length character string

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

variable-length character string

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

variable-length character string

bytea :: TypeExpression (NoDef :=> Null PGbytea) Source #

binary data ("byte array")

timestamp :: TypeExpression (NoDef :=> Null PGtimestamp) Source #

date and time (no time zone)

timestampWithTimeZone :: TypeExpression (NoDef :=> Null PGtimestamptz) Source #

date and time, including time zone

date :: TypeExpression (NoDef :=> Null PGdate) Source #

calendar date (year, month, day)

time :: TypeExpression (NoDef :=> Null PGtime) Source #

time of day (no time zone)

timeWithTimeZone :: TypeExpression (NoDef :=> Null PGtimetz) Source #

time of day, including time zone

uuid :: TypeExpression (NoDef :=> Null PGuuid) Source #

universally unique identifier

inet :: TypeExpression (NoDef :=> Null PGinet) Source #

IPv4 or IPv6 host address

json :: TypeExpression (NoDef :=> Null PGjson) Source #

textual JSON data

jsonb :: TypeExpression (NoDef :=> Null PGjsonb) Source #

binary JSON data, decomposed

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

fixed length array

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

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

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

default_ :: Expression '[] Ungrouped '[] ty -> TypeExpression (NoDef :=> ty) -> TypeExpression (Def :=> 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 #

HTraverse_ k [k] (NP k) 

Methods

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

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

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

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

htraverse' :: (SListIN (NP k) l h xs, Applicative g) => (forall (a :: NP k). f a -> g (f' a)) -> h f xs -> g (h f' 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