squeal-postgresql-0.3.0.0: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.Expression

Contents

Description

Squeal expressions are the atoms used to build statements.

Synopsis

Expression

newtype Expression (schema :: SchemaType) (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 (NP (Symbol, NullityType) (Aliased NullityType (Expression schema relations (Grouped bys) params)) ((:) (Symbol, NullityType) ((:::) NullityType column ty) ([] (Symbol, NullityType)))) Source # 

Methods

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

(Has [(Symbol, NullityType)] relation relations columns, Has NullityType column columns ty, GroupedBy [(Symbol, Symbol)] relation column bys) => IsQualified relation column (Aliased NullityType (Expression schema relations (Grouped bys) params) ((:::) NullityType column ty)) Source # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

fromLabel :: Expression schema relations Ungrouped params ty #

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

Methods

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

Eq (Expression schema relations grouping params ty) Source # 

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 # 

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 # 

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 # 

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 # 

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 # 

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 # 

Methods

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

Generic (Expression schema relations grouping params ty) Source # 

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 params (nullity PGtext)) Source # 

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 # 

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 # 

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 # 

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 # 

Methods

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

RenderSQL (Expression schema relations grouping params ty) Source # 

Methods

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

type Rep (Expression schema relations grouping params ty) Source # 
type Rep (Expression schema relations grouping params ty) = D1 * (MetaData "Expression" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.3.0.0-E9Ax8VffdgQ3ZC5pqeEIaA" True) (C1 * (MetaCons "UnsafeExpression" PrefixI True) (S1 * (MetaSel (Just Symbol "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 ((:) NullityType ty' params) ty Source # 

Methods

parameter :: TypeExpression schema (PGTypeOf ty) -> Expression schema relations grouping ((NullityType ': ty') params) ty Source #

HasParameter 1 schema ((:) NullityType ty1 tys) ty1 Source # 

Methods

parameter :: TypeExpression schema (PGTypeOf ty1) -> Expression schema relations grouping ((NullityType ': 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 :* Nil) :: 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)

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%')

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,avgDistinct Source #

Arguments

:: Expression schema relations Ungrouped params (nullity ty)

what to average

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

Instances

PGAvg PGType PGint2 PGnumeric Source # 

Methods

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

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

PGAvg PGType PGint4 PGnumeric Source # 

Methods

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

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

PGAvg PGType PGint8 PGnumeric Source # 

Methods

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

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

PGAvg PGType PGnumeric PGnumeric Source # 

Methods

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

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

PGAvg PGType PGfloat4 PGfloat8 Source # 

Methods

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

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

PGAvg PGType PGfloat8 PGfloat8 Source # 

Methods

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

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

PGAvg PGType PGinterval PGinterval Source # 

Methods

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

avgDistinct :: Expression schema relations Ungrouped params (nullity PGinterval) -> Expression schema relations (Grouped bys) params (nullity avg) 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 SchemumType alias schema (Typedef ty) => IsLabel alias (TypeExpression schema ty) Source # 

Methods

fromLabel :: TypeExpression schema ty #

Eq (TypeExpression schema ty) Source # 

Methods

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

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

Ord (TypeExpression schema ty) Source # 

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 # 

Methods

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

show :: TypeExpression schema ty -> String #

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

Generic (TypeExpression schema ty) Source # 

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 # 

Methods

rnf :: TypeExpression schema ty -> () #

type Rep (TypeExpression schema ty) Source # 
type Rep (TypeExpression schema ty) = D1 * (MetaData "TypeExpression" "Squeal.PostgreSQL.Expression" "squeal-postgresql-0.3.0.0-E9Ax8VffdgQ3ZC5pqeEIaA" True) (C1 * (MetaCons "UnsafeTypeExpression" PrefixI True) (S1 * (MetaSel (Just Symbol "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 # 
PGTyped schema PGjson Source # 
PGTyped schema PGuuid Source # 
PGTyped schema PGinterval Source # 
PGTyped schema PGtimetz Source # 
PGTyped schema PGtime Source # 
PGTyped schema PGdate Source # 
PGTyped schema PGtimestamptz Source # 
PGTyped schema PGtimestamp Source # 
PGTyped schema PGbytea Source # 
PGTyped schema PGtext Source # 
PGTyped schema PGfloat8 Source # 
PGTyped schema PGfloat4 Source # 
PGTyped schema PGnumeric Source # 
PGTyped schema PGint8 Source # 
PGTyped schema PGint4 Source # 
PGTyped schema PGint2 Source # 
PGTyped schema PGbool Source # 
PGTyped schema ty => PGTyped schema (PGvararray ty) Source # 

Methods

pgtype :: TypeExpression schema (PGvararray ty) Source #

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

Methods

pgtype :: TypeExpression schema (PGvarchar n) Source #

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

Methods

pgtype :: TypeExpression schema (PGchar n) Source #

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

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

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

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

Methods

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

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

Methods

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

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

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

Methods

fromLabel :: NP Symbol Alias aliases #

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

Methods

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

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

Methods

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

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