Copyright | (c) Eitan Chatav 2017 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Expression
Description
Squeal expressions are the atoms used to build statements.
- newtype Expression (tables :: TablesType) (grouping :: Grouping) (params :: [ColumnType]) (ty :: ColumnType) = UnsafeExpression {}
- class (PGTyped (BaseType ty), KnownNat n) => HasParameter (n :: Nat) params ty | n params -> ty where
- class KnownSymbol column => HasColumn column columns ty | column columns -> ty where
- data Column (columns :: ColumnsType) (columnty :: (Symbol, ColumnType)) where
- renderColumn :: Column columns columnty -> ByteString
- class (KnownSymbol table, KnownSymbol column) => GroupedBy table column bys where
- def :: Expression '[] Ungrouped params (Optional (nullity ty))
- unDef :: Expression '[] Ungrouped params (Required (nullity ty)) -> Expression '[] Ungrouped params (Optional (nullity ty))
- null_ :: Expression tables grouping params (optionality (Null ty))
- unNull :: Expression tables grouping params (optionality (NotNull ty)) -> Expression tables grouping params (optionality (Null ty))
- coalesce :: [Expression tables grouping params (Required (Null ty))] -> Expression tables grouping params (Required (NotNull ty)) -> Expression tables grouping params (Required (NotNull ty))
- fromNull :: Expression tables grouping params (Required (NotNull ty)) -> Expression tables grouping params (Required (Null ty)) -> Expression tables grouping params (Required (NotNull ty))
- isNull :: Expression tables grouping params (Required (Null ty)) -> Condition tables grouping params
- isn'tNull :: Expression tables grouping params (Required (Null ty)) -> Condition tables grouping params
- matchNull :: Expression tables grouping params (Required nullty) -> (Expression tables grouping params (Required (NotNull ty)) -> Expression tables grouping params (Required nullty)) -> Expression tables grouping params (Required (Null ty)) -> Expression tables grouping params (Required nullty)
- nullIf :: Expression tables grouping params (Required (NotNull ty)) -> Expression tables grouping params (Required (NotNull ty)) -> Expression tables grouping params (Required (Null ty))
- unsafeBinaryOp :: ByteString -> Expression tables grouping params (Required ty0) -> Expression tables grouping params (Required ty1) -> Expression tables grouping params (Required ty2)
- unsafeUnaryOp :: ByteString -> Expression tables grouping params (Required ty0) -> Expression tables grouping params (Required ty1)
- unsafeFunction :: ByteString -> Expression tables grouping params (Required xty) -> Expression tables grouping params (Required yty)
- atan2_ :: PGFloating float => Expression tables grouping params (Required (nullity float)) -> Expression tables grouping params (Required (nullity float)) -> Expression tables grouping params (Required (nullity float))
- cast :: TypeExpression (Required (Null ty1)) -> Expression tables grouping params (Required (nullity ty0)) -> Expression tables grouping params (Required (nullity ty1))
- quot_ :: PGIntegral int => Expression tables grouping params (Required (nullity int)) -> Expression tables grouping params (Required (nullity int)) -> Expression tables grouping params (Required (nullity int))
- rem_ :: PGIntegral int => Expression tables grouping params (Required (nullity int)) -> Expression tables grouping params (Required (nullity int)) -> Expression tables grouping params (Required (nullity int))
- trunc :: PGFloating frac => Expression tables grouping params (Required (nullity frac)) -> Expression tables grouping params (Required (nullity frac))
- round_ :: PGFloating frac => Expression tables grouping params (Required (nullity frac)) -> Expression tables grouping params (Required (nullity frac))
- ceiling_ :: PGFloating frac => Expression tables grouping params (Required (nullity frac)) -> Expression tables grouping params (Required (nullity frac))
- greatest :: Expression tables grouping params (Required nullty) -> [Expression tables grouping params (Required nullty)] -> Expression tables grouping params (Required nullty)
- least :: Expression tables grouping params (Required nullty) -> [Expression tables grouping params (Required nullty)] -> Expression tables grouping params (Required nullty)
- type Condition tables grouping params = Expression tables grouping params (Required (NotNull PGbool))
- true :: Condition tables grouping params
- false :: Condition tables grouping params
- not_ :: Condition tables grouping params -> Condition tables grouping params
- (.&&) :: Condition tables grouping params -> Condition tables grouping params -> Condition tables grouping params
- (.||) :: Condition tables grouping params -> Condition tables grouping params -> Condition tables grouping params
- caseWhenThenElse :: [(Condition tables grouping params, Expression tables grouping params (Required ty))] -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty)
- ifThenElse :: Condition tables grouping params -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty)
- (.==) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity PGbool))
- (./=) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity PGbool))
- (.>=) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity PGbool))
- (.<) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity PGbool))
- (.<=) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity PGbool))
- (.>) :: Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity ty)) -> Expression tables grouping params (Required (nullity PGbool))
- currentDate :: Expression tables grouping params (Required (nullity PGdate))
- currentTime :: Expression tables grouping params (Required (nullity PGtimetz))
- currentTimestamp :: Expression tables grouping params (Required (nullity PGtimestamptz))
- localTime :: Expression tables grouping params (Required (nullity PGtime))
- localTimestamp :: Expression tables grouping params (Required (nullity PGtimestamp))
- lower :: Expression tables grouping params (Required (nullity PGtext)) -> Expression tables grouping params (Required (nullity PGtext))
- upper :: Expression tables grouping params (Required (nullity PGtext)) -> Expression tables grouping params (Required (nullity PGtext))
- charLength :: Expression tables grouping params (Required (nullity PGtext)) -> Expression tables grouping params (Required (nullity PGint4))
- like :: Expression tables grouping params (Required (nullity PGtext)) -> Expression tables grouping params (Required (nullity PGtext)) -> Expression tables grouping params (Required (nullity PGbool))
- unsafeAggregate :: ByteString -> Expression tables Ungrouped params (Required xty) -> Expression tables (Grouped bys) params (Required yty)
- unsafeAggregateDistinct :: ByteString -> Expression tables Ungrouped params (Required xty) -> Expression tables (Grouped bys) params (Required yty)
- sum_ :: PGNum ty => Expression tables Ungrouped params (Required (nullity ty)) -> Expression tables (Grouped bys) params (Required (nullity ty))
- sumDistinct :: PGNum ty => Expression tables Ungrouped params (Required (nullity ty)) -> Expression tables (Grouped bys) params (Required (nullity ty))
- class PGAvg ty avg | ty -> avg where
- bitAnd :: PGIntegral int => Expression tables Ungrouped params (Required (nullity int)) -> Expression tables (Grouped bys) params (Required (nullity int))
- bitOr :: PGIntegral int => Expression tables Ungrouped params (Required (nullity int)) -> Expression tables (Grouped bys) params (Required (nullity int))
- boolAnd :: Expression tables Ungrouped params (Required (nullity PGbool)) -> Expression tables (Grouped bys) params (Required (nullity PGbool))
- boolOr :: Expression tables Ungrouped params (Required (nullity PGbool)) -> Expression tables (Grouped bys) params (Required (nullity PGbool))
- bitAndDistinct :: PGIntegral int => Expression tables Ungrouped params (Required (nullity int)) -> Expression tables (Grouped bys) params (Required (nullity int))
- bitOrDistinct :: PGIntegral int => Expression tables Ungrouped params (Required (nullity int)) -> Expression tables (Grouped bys) params (Required (nullity int))
- boolAndDistinct :: Expression tables Ungrouped params (Required (nullity PGbool)) -> Expression tables (Grouped bys) params (Required (nullity PGbool))
- boolOrDistinct :: Expression tables Ungrouped params (Required (nullity PGbool)) -> Expression tables (Grouped bys) params (Required (nullity PGbool))
- countStar :: Expression tables (Grouped bys) params (Required (NotNull PGint8))
- count :: Expression tables Ungrouped params (Required ty) -> Expression tables (Grouped bys) params (Required (NotNull PGint8))
- countDistinct :: Expression tables Ungrouped params (Required ty) -> Expression tables (Grouped bys) params (Required (NotNull PGint8))
- every :: Expression tables Ungrouped params (Required (nullity PGbool)) -> Expression tables (Grouped bys) params (Required (nullity PGbool))
- everyDistinct :: Expression tables Ungrouped params (Required (nullity PGbool)) -> Expression tables (Grouped bys) params (Required (nullity PGbool))
- max_ :: Expression tables Ungrouped params (Required (nullity ty)) -> Expression tables (Grouped bys) params (Required (nullity ty))
- maxDistinct :: Expression tables Ungrouped params (Required (nullity ty)) -> Expression tables (Grouped bys) params (Required (nullity ty))
- min_ :: Expression tables Ungrouped params (Required (nullity ty)) -> Expression tables (Grouped bys) params (Required (nullity ty))
- minDistinct :: Expression tables Ungrouped params (Required (nullity ty)) -> Expression tables (Grouped bys) params (Required (nullity ty))
- newtype Table (schema :: TablesType) (columns :: ColumnsType) = UnsafeTable {}
- class KnownSymbol table => HasTable table tables columns | table tables -> columns where
- newtype TypeExpression (ty :: ColumnType) = UnsafeTypeExpression {}
- class PGTyped (ty :: PGType) where
- bool :: TypeExpression (Required (Null PGbool))
- int2 :: TypeExpression (Required (Null PGint2))
- smallint :: TypeExpression (Required (Null PGint2))
- int4 :: TypeExpression (Required (Null PGint4))
- int :: TypeExpression (Required (Null PGint4))
- integer :: TypeExpression (Required (Null PGint4))
- int8 :: TypeExpression (Required (Null PGint8))
- bigint :: TypeExpression (Required (Null PGint8))
- numeric :: TypeExpression (Required (Null PGnumeric))
- float4 :: TypeExpression (Required (Null PGfloat4))
- real :: TypeExpression (Required (Null PGfloat4))
- float8 :: TypeExpression (Required (Null PGfloat8))
- doublePrecision :: TypeExpression (Required (Null PGfloat8))
- serial2 :: TypeExpression (Optional (NotNull PGint2))
- smallserial :: TypeExpression (Optional (NotNull PGint2))
- serial4 :: TypeExpression (Optional (NotNull PGint4))
- serial :: TypeExpression (Optional (NotNull PGint4))
- serial8 :: TypeExpression (Optional (NotNull PGint8))
- bigserial :: TypeExpression (Optional (NotNull PGint8))
- text :: TypeExpression (Required (Null PGtext))
- char :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression (Required (Null (PGchar n)))
- character :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression (Required (Null (PGchar n)))
- varchar :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression (Required (Null (PGvarchar n)))
- characterVarying :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression (Required (Null (PGvarchar n)))
- bytea :: TypeExpression (Required (Null PGbytea))
- timestamp :: TypeExpression (Required (Null PGtimestamp))
- timestampWithTimeZone :: TypeExpression (Required (Null PGtimestamptz))
- date :: TypeExpression (Required (Null PGdate))
- time :: TypeExpression (Required (Null PGtime))
- timeWithTimeZone :: TypeExpression (Required (Null PGtimetz))
- interval :: TypeExpression (Required (Null PGinterval))
- uuid :: TypeExpression (Required (Null PGuuid))
- inet :: TypeExpression (Required (Null PGinet))
- json :: TypeExpression (Required (Null PGjson))
- jsonb :: TypeExpression (Required (Null PGjsonb))
- notNull :: TypeExpression (optionality (Null ty)) -> TypeExpression (optionality (NotNull ty))
- default_ :: Expression '[] Ungrouped '[] (Required ty) -> TypeExpression (Required ty) -> TypeExpression (Optional ty)
- (&) :: a -> (a -> b) -> b
- data NP k (a :: k -> *) (b :: [k]) :: forall k. (k -> *) -> [k] -> * where
Expression
newtype Expression (tables :: TablesType) (grouping :: Grouping) (params :: [ColumnType]) (ty :: ColumnType) Source #
Expression
s are used in a variety of contexts,
such as in the target list of the select
command,
as new column values in insertInto
or update
,
or in search Condition
s in a number of commands.
The expression syntax allows the calculation of values from primitive expression using arithmetic, logical, and other operations.
Constructors
UnsafeExpression | |
Fields |
Instances
(HasTable table tables columns, HasColumn column columns ty, GroupedBy table column bys) => IsTableColumn table column (Expression tables (Grouped bys) params ty) Source # | |
(HasTable table tables columns, HasColumn column columns ty) => IsTableColumn table column (Expression tables Ungrouped params ty) Source # | |
(HasUnique ColumnsType table tables columns, HasColumn column columns ty, GroupedBy table column bys) => IsLabel column (Expression tables (Grouped bys) params ty) Source # | |
(HasColumn column columns ty, HasUnique ColumnsType table tables columns) => IsLabel column (Expression tables Ungrouped params ty) Source # | |
Eq (Expression tables grouping params ty) Source # | |
(PGNum ty, PGFloating ty) => Floating (Expression tables grouping params (Required (nullity ty))) Source # | |
(PGNum ty, PGFloating ty) => Fractional (Expression tables grouping params (Required (nullity ty))) Source # | |
PGNum ty => Num (Expression tables grouping params (Required (nullity ty))) Source # | |
Ord (Expression tables grouping params ty) Source # | |
Show (Expression tables grouping params ty) Source # | |
IsString (Expression tables grouping params (Required (nullity PGtext))) Source # | |
Generic (Expression tables grouping params ty) Source # | |
Monoid (Expression tables grouping params (Required (nullity PGtext))) Source # | |
NFData (Expression tables grouping params ty) Source # | |
type Rep (Expression tables grouping params ty) Source # | |
class (PGTyped (BaseType ty), KnownNat n) => HasParameter (n :: Nat) params ty | n params -> ty where Source #
A HasParameter
constraint is used to indicate a value that is
supplied externally to a SQL statement.
manipulateParams
,
queryParams
and
traversePrepared
support specifying data values
separately from the SQL command string, in which case param
s are used to
refer to the out-of-line data values.
Methods
param :: Expression tables grouping params ty Source #
Instances
(KnownNat n, HasParameter ((-) n 1) params ty) => HasParameter n ((:) ColumnType ty' params) ty Source # | |
PGTyped (BaseType ty1) => HasParameter 1 ((:) ColumnType ty1 tys) ty1 Source # | |
class KnownSymbol column => HasColumn column columns ty | column columns -> ty where Source #
A HasColumn
constraint indicates an unqualified column reference.
getColumn
can only be unambiguous when the TableExpression
the column
references is unique, in which case the column may be referenced using
-XOverloadedLabels
. Otherwise, combined with a HasTable
constraint, the
qualified column reference operator !
may be used.
Methods
getColumn :: HasUnique table tables columns => Alias column -> Expression tables Ungrouped params ty Source #
Instances
(KnownSymbol column, HasColumn column table ty) => HasColumn column ((:) (Symbol, ColumnType) ty' table) ty Source # | |
KnownSymbol column => HasColumn column ((:) (Symbol, ColumnType) ((:::) ColumnType column (optionality ty)) tys) (Required ty) Source # | |
data Column (columns :: ColumnsType) (columnty :: (Symbol, ColumnType)) where Source #
A Column
is a witness to a HasColumn
constraint. It's used
in unique
and other
TableConstraint
s to witness a
subcolumns relationship.
renderColumn :: Column columns columnty -> ByteString Source #
Render a Column
.
class (KnownSymbol table, KnownSymbol column) => GroupedBy table column bys where Source #
A GroupedBy
constraint indicates that a table qualified column is
a member of the auxiliary namespace created by GROUP BY
clauses and thus,
may be called in an output Expression
without aggregating.
Methods
getGroup1 :: (HasUnique table tables columns, HasColumn column columns ty) => Alias column -> Expression tables (Grouped bys) params ty Source #
getGroup2 :: (HasTable table tables columns, HasColumn column columns ty) => Alias table -> Alias column -> Expression tables (Grouped bys) params ty Source #
Instances
(KnownSymbol table, KnownSymbol column, GroupedBy table column bys) => GroupedBy table column ((:) (Symbol, Symbol) tabcol bys) Source # | |
(KnownSymbol table, KnownSymbol column) => GroupedBy table column ((:) (Symbol, Symbol) ((,) Symbol Symbol table column) bys) Source # | |
Default
def :: Expression '[] Ungrouped params (Optional (nullity ty)) Source #
>>>
renderExpression def
"DEFAULT"
Arguments
:: Expression '[] Ungrouped params (Required (nullity ty)) | not |
-> Expression '[] Ungrouped params (Optional (nullity ty)) |
>>>
renderExpression $ unDef false
"FALSE"
Null
null_ :: Expression tables grouping params (optionality (Null ty)) Source #
analagous to Nothing
>>>
renderExpression $ null_
"NULL"
Arguments
:: Expression tables grouping params (optionality (NotNull ty)) | not |
-> Expression tables grouping params (optionality (Null ty)) |
analagous to Just
>>>
renderExpression $ unNull true
"TRUE"
Arguments
:: [Expression tables grouping params (Required (Null ty))] |
|
-> Expression tables grouping params (Required (NotNull ty)) |
|
-> Expression tables grouping params (Required (NotNull ty)) |
return the leftmost value which is not NULL
>>>
renderExpression $ coalesce [null_, unNull true] false
"COALESCE(NULL, TRUE, FALSE)"
Arguments
:: Expression tables grouping params (Required (NotNull ty)) | what to convert |
-> Expression tables grouping params (Required (Null ty)) | |
-> Expression tables grouping params (Required (NotNull ty)) |
analagous to fromMaybe
using COALESCE
>>>
renderExpression $ fromNull true null_
"COALESCE(NULL, TRUE)"
Arguments
:: Expression tables grouping params (Required (Null ty)) | possibly |
-> Condition tables grouping params |
>>>
renderExpression $ null_ & isNull
"NULL IS NULL"
Arguments
:: Expression tables grouping params (Required (Null ty)) | possibly |
-> Condition tables grouping params |
>>>
renderExpression $ null_ & isn'tNull
"NULL IS NOT NULL"
Arguments
:: Expression tables grouping params (Required nullty) | what to convert |
-> (Expression tables grouping params (Required (NotNull ty)) -> Expression tables grouping params (Required nullty)) | function to perform when |
-> Expression tables grouping params (Required (Null ty)) | |
-> Expression tables grouping params (Required nullty) |
analagous to maybe
using IS NULL
>>>
renderExpression $ matchNull true not_ null_
"CASE WHEN NULL IS NULL THEN TRUE ELSE (NOT NULL) END"
Arguments
:: Expression tables grouping params (Required (NotNull ty)) |
|
-> Expression tables grouping params (Required (NotNull ty)) |
|
-> Expression tables grouping params (Required (Null ty)) |
Functions
Arguments
:: ByteString | operator |
-> Expression tables grouping params (Required ty0) | |
-> Expression tables grouping params (Required ty1) | |
-> Expression tables grouping params (Required ty2) |
>>>
renderExpression $ unsafeBinaryOp "OR" true false
"(TRUE OR FALSE)"
Arguments
:: ByteString | operator |
-> Expression tables grouping params (Required ty0) | |
-> Expression tables grouping params (Required ty1) |
>>>
renderExpression $ unsafeUnaryOp "NOT" true
"(NOT TRUE)"
Arguments
:: ByteString | function |
-> Expression tables grouping params (Required xty) | |
-> Expression tables grouping params (Required yty) |
>>>
renderExpression $ unsafeFunction "f" true
"f(TRUE)"
Arguments
:: PGFloating float | |
=> Expression tables grouping params (Required (nullity float)) | numerator |
-> Expression tables grouping params (Required (nullity float)) | denominator |
-> Expression tables grouping params (Required (nullity float)) |
>>>
renderExpression @_ @_ @_ @(_ (_ 'PGfloat4)) $ atan2_ pi 2
"atan2(pi(), 2)"
Arguments
:: TypeExpression (Required (Null ty1)) | type to cast as |
-> Expression tables grouping params (Required (nullity ty0)) | value to convert |
-> Expression tables grouping params (Required (nullity ty1)) |
>>>
renderExpression $ true & cast int4
"(TRUE :: int4)"
Arguments
:: PGIntegral int | |
=> Expression tables grouping params (Required (nullity int)) | numerator |
-> Expression tables grouping params (Required (nullity int)) | denominator |
-> Expression tables grouping params (Required (nullity int)) |
integer division, truncates the result
>>>
renderExpression @_ @_ @_ @(_(_ 'PGint2)) $ 5 `quot_` 2
"(5 / 2)"
Arguments
:: PGIntegral int | |
=> Expression tables grouping params (Required (nullity int)) | numerator |
-> Expression tables grouping params (Required (nullity int)) | denominator |
-> Expression tables grouping params (Required (nullity int)) |
remainder upon integer division
>>>
renderExpression @_ @_ @_ @(_ (_ 'PGint2)) $ 5 `rem_` 2
"(5 % 2)"
Arguments
:: PGFloating frac | |
=> Expression tables grouping params (Required (nullity frac)) | fractional number |
-> Expression tables grouping params (Required (nullity frac)) |
>>>
renderExpression @_ @_ @_ @(_ (_ 'PGfloat4)) $ trunc pi
"trunc(pi())"
Arguments
:: PGFloating frac | |
=> Expression tables grouping params (Required (nullity frac)) | fractional number |
-> Expression tables grouping params (Required (nullity frac)) |
>>>
renderExpression @_ @_ @_ @(_ (_ 'PGfloat4)) $ round_ pi
"round(pi())"
Arguments
:: PGFloating frac | |
=> Expression tables grouping params (Required (nullity frac)) | fractional number |
-> Expression tables grouping params (Required (nullity frac)) |
>>>
renderExpression @_ @_ @_ @(_ (_ 'PGfloat4)) $ ceiling_ pi
"ceiling(pi())"
Arguments
:: Expression tables grouping params (Required nullty) | needs at least 1 argument |
-> [Expression tables grouping params (Required nullty)] | or more |
-> Expression tables grouping params (Required nullty) |
>>>
renderExpression @_ @_ @'[_] $ greatest currentTimestamp [param @1]
"GREATEST(CURRENT_TIMESTAMP, ($1 :: timestamp with time zone))"
Arguments
:: Expression tables grouping params (Required nullty) | needs at least 1 argument |
-> [Expression tables grouping params (Required nullty)] | or more |
-> Expression tables grouping params (Required nullty) |
>>>
renderExpression $ least currentTimestamp [null_]
"LEAST(CURRENT_TIMESTAMP, NULL)"
Conditions
type Condition tables grouping params = Expression tables grouping params (Required (NotNull PGbool)) Source #
A Condition
is a boolean valued Expression
. While SQL allows
conditions to have NULL
, squeal instead chooses to disallow NULL
,
forcing one to handle the case of NULL
explicitly to produce
a Condition
.
not_ :: Condition tables grouping params -> Condition tables grouping params Source #
>>>
renderExpression $ not_ true
"(NOT TRUE)"
(.&&) :: Condition tables grouping params -> Condition tables grouping params -> Condition tables grouping params Source #
>>>
renderExpression $ true .&& false
"(TRUE AND FALSE)"
(.||) :: Condition tables grouping params -> Condition tables grouping params -> Condition tables grouping params Source #
>>>
renderExpression $ true .|| false
"(TRUE OR FALSE)"
caseWhenThenElse :: [(Condition tables grouping params, Expression tables grouping params (Required ty))] -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty) Source #
>>>
renderExpression @_ @_ @_ @(_ (_ 'PGint2)) $ caseWhenThenElse [(true, 1), (false, 2)] 3
"CASE WHEN TRUE THEN 1 WHEN FALSE THEN 2 ELSE 3 END"
ifThenElse :: Condition tables grouping params -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty) -> Expression tables grouping params (Required ty) Source #
>>>
renderExpression @_ @_ @_ @(_ (_ 'PGint2)) $ ifThenElse true 1 0
"CASE WHEN TRUE THEN 1 ELSE 0 END"
Arguments
:: Expression tables grouping params (Required (nullity ty)) | lhs |
-> Expression tables grouping params (Required (nullity ty)) | rhs |
-> Expression tables grouping params (Required (nullity PGbool)) |
Arguments
:: Expression tables grouping params (Required (nullity ty)) | lhs |
-> Expression tables grouping params (Required (nullity ty)) | rhs |
-> Expression tables grouping params (Required (nullity PGbool)) |
>>>
renderExpression $ unNull true ./= null_
"(TRUE <> NULL)"
Arguments
:: Expression tables grouping params (Required (nullity ty)) | lhs |
-> Expression tables grouping params (Required (nullity ty)) | rhs |
-> Expression tables grouping params (Required (nullity PGbool)) |
>>>
renderExpression $ unNull true .>= null_
"(TRUE >= NULL)"
Arguments
:: Expression tables grouping params (Required (nullity ty)) | lhs |
-> Expression tables grouping params (Required (nullity ty)) | rhs |
-> Expression tables grouping params (Required (nullity PGbool)) |
>>>
renderExpression $ unNull true .< null_
"(TRUE < NULL)"
Arguments
:: Expression tables grouping params (Required (nullity ty)) | lhs |
-> Expression tables grouping params (Required (nullity ty)) | rhs |
-> Expression tables grouping params (Required (nullity PGbool)) |
>>>
renderExpression $ unNull true .<= null_
"(TRUE <= NULL)"
Arguments
:: Expression tables grouping params (Required (nullity ty)) | lhs |
-> Expression tables grouping params (Required (nullity ty)) | rhs |
-> Expression tables grouping params (Required (nullity PGbool)) |
>>>
renderExpression $ unNull true .> null_
"(TRUE > NULL)"
Time
currentDate :: Expression tables grouping params (Required (nullity PGdate)) Source #
>>>
renderExpression $ currentDate
"CURRENT_DATE"
currentTime :: Expression tables grouping params (Required (nullity PGtimetz)) Source #
>>>
renderExpression $ currentTime
"CURRENT_TIME"
currentTimestamp :: Expression tables grouping params (Required (nullity PGtimestamptz)) Source #
>>>
renderExpression $ currentTimestamp
"CURRENT_TIMESTAMP"
localTime :: Expression tables grouping params (Required (nullity PGtime)) Source #
>>>
renderExpression $ localTime
"LOCALTIME"
localTimestamp :: Expression tables grouping params (Required (nullity PGtimestamp)) Source #
>>>
renderExpression $ localTimestamp
"LOCALTIMESTAMP"
Text
Arguments
:: Expression tables grouping params (Required (nullity PGtext)) | string to lower case |
-> Expression tables grouping params (Required (nullity PGtext)) |
>>>
renderExpression $ lower "ARRRGGG"
"lower(E'ARRRGGG')"
Arguments
:: Expression tables grouping params (Required (nullity PGtext)) | string to upper case |
-> Expression tables grouping params (Required (nullity PGtext)) |
>>>
renderExpression $ upper "eeee"
"upper(E'eeee')"
Arguments
:: Expression tables grouping params (Required (nullity PGtext)) | string to measure |
-> Expression tables grouping params (Required (nullity PGint4)) |
>>>
renderExpression $ charLength "four"
"char_length(E'four')"
Arguments
:: Expression tables grouping params (Required (nullity PGtext)) | string |
-> Expression tables grouping params (Required (nullity PGtext)) | pattern |
-> Expression tables grouping params (Required (nullity PGbool)) |
The like
expression returns true if the string
matches
the supplied pattern
. If pattern
does not contain percent signs
or underscores, then the pattern only represents the string itself;
in that case like
acts like the equals operator. An underscore (_)
in pattern stands for (matches) any single character; a percent sign (%)
matches any sequence of zero or more characters.
>>>
renderExpression $ "abc" `like` "a%"
"(E'abc' LIKE E'a%')"
Aggregation
Arguments
:: ByteString | aggregate function |
-> Expression tables Ungrouped params (Required xty) | |
-> Expression tables (Grouped bys) params (Required yty) |
escape hatch to define aggregate functions
unsafeAggregateDistinct Source #
Arguments
:: ByteString | aggregate function |
-> Expression tables Ungrouped params (Required xty) | |
-> Expression tables (Grouped bys) params (Required yty) |
escape hatch to define aggregate functions over distinct values
Arguments
:: PGNum ty | |
=> Expression tables Ungrouped params (Required (nullity ty)) | what to sum |
-> Expression tables (Grouped bys) params (Required (nullity ty)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGnumeric)]] $ sum_ #col
"sum(col)"
Arguments
:: PGNum ty | |
=> Expression tables Ungrouped params (Required (nullity ty)) | what to sum |
-> Expression tables (Grouped bys) params (Required (nullity ty)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGnumeric)]] $ sumDistinct #col
"sum(DISTINCT col)"
class PGAvg ty avg | ty -> avg where Source #
Methods
Arguments
:: Expression tables Ungrouped params (Required (nullity ty)) | what to average |
-> Expression tables (Grouped bys) params (Required (nullity avg)) |
Arguments
:: PGIntegral int | |
=> Expression tables Ungrouped params (Required (nullity int)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity int)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGint4)]] $ bitAnd #col
"bit_and(col)"
Arguments
:: PGIntegral int | |
=> Expression tables Ungrouped params (Required (nullity int)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity int)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGint4)]] $ bitOr #col
"bit_or(col)"
Arguments
:: Expression tables Ungrouped params (Required (nullity PGbool)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity PGbool)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ boolAnd #col
"bool_and(col)"
Arguments
:: Expression tables Ungrouped params (Required (nullity PGbool)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity PGbool)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ boolOr #col
"bool_or(col)"
Arguments
:: PGIntegral int | |
=> Expression tables Ungrouped params (Required (nullity int)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity int)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGint4)]] $ bitAndDistinct #col
"bit_and(DISTINCT col)"
Arguments
:: PGIntegral int | |
=> Expression tables Ungrouped params (Required (nullity int)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity int)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGint4)]] $ bitOrDistinct #col
"bit_or(DISTINCT col)"
Arguments
:: Expression tables Ungrouped params (Required (nullity PGbool)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity PGbool)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ boolAndDistinct #col
"bool_and(DISTINCT col)"
Arguments
:: Expression tables Ungrouped params (Required (nullity PGbool)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity PGbool)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ boolOrDistinct #col
"bool_or(DISTINCT col)"
countStar :: Expression tables (Grouped bys) params (Required (NotNull PGint8)) Source #
A special aggregation that does not require an input
>>>
renderExpression countStar
"count(*)"
Arguments
:: Expression tables Ungrouped params (Required ty) | what to count |
-> Expression tables (Grouped bys) params (Required (NotNull PGint8)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Optional _]] $ count #col
"count(col)"
Arguments
:: Expression tables Ungrouped params (Required ty) | what to count |
-> Expression tables (Grouped bys) params (Required (NotNull PGint8)) |
>>>
renderExpression @'[_ ::: '["col" ::: 'Required _]] $ countDistinct #col
"count(DISTINCT col)"
Arguments
:: Expression tables Ungrouped params (Required (nullity PGbool)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity PGbool)) |
synonym for boolAnd
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ every #col
"every(col)"
Arguments
:: Expression tables Ungrouped params (Required (nullity PGbool)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity PGbool)) |
synonym for boolAndDistinct
>>>
renderExpression @'[_ ::: '["col" ::: 'Required (_ 'PGbool)]] $ everyDistinct #col
"every(DISTINCT col)"
Arguments
:: Expression tables Ungrouped params (Required (nullity ty)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity ty)) |
minimum and maximum aggregation
Arguments
:: Expression tables Ungrouped params (Required (nullity ty)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity ty)) |
minimum and maximum aggregation
Arguments
:: Expression tables Ungrouped params (Required (nullity ty)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity ty)) |
minimum and maximum aggregation
Arguments
:: Expression tables Ungrouped params (Required (nullity ty)) | what to aggregate |
-> Expression tables (Grouped bys) params (Required (nullity ty)) |
minimum and maximum aggregation
Tables
newtype Table (schema :: TablesType) (columns :: ColumnsType) Source #
A Table
from a schema without its alias with an IsLabel
instance
to call a table reference by its alias.
Constructors
UnsafeTable | |
Fields |
Instances
HasTable table schema columns => IsLabel table (Table schema columns) Source # | |
Eq (Table schema columns) Source # | |
Ord (Table schema columns) Source # | |
Show (Table schema columns) Source # | |
Generic (Table schema columns) Source # | |
NFData (Table schema columns) Source # | |
type Rep (Table schema columns) Source # | |
class KnownSymbol table => HasTable table tables columns | table tables -> columns where Source #
A HasTable
constraint indicates a table reference.
Instances
(KnownSymbol table, HasTable table schema columns) => HasTable table ((:) (Symbol, ColumnsType) table' schema) columns Source # | |
KnownSymbol table => HasTable table ((:) (Symbol, ColumnsType) ((:::) ColumnsType table columns) tables) columns Source # | |
TypeExpression
newtype TypeExpression (ty :: ColumnType) Source #
TypeExpression
s are used in cast
s and createTable
commands.
Constructors
UnsafeTypeExpression | |
Fields |
Instances
Eq (TypeExpression ty) Source # | |
Ord (TypeExpression ty) Source # | |
Show (TypeExpression ty) Source # | |
Generic (TypeExpression ty) Source # | |
NFData (TypeExpression ty) Source # | |
type Rep (TypeExpression ty) Source # | |
class PGTyped (ty :: PGType) where Source #
Minimal complete definition
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 # | |
float4 :: TypeExpression (Required (Null PGfloat4)) Source #
single precision floating-point number (4 bytes)
real :: TypeExpression (Required (Null PGfloat4)) Source #
single precision floating-point number (4 bytes)
float8 :: TypeExpression (Required (Null PGfloat8)) Source #
double precision floating-point number (8 bytes)
doublePrecision :: TypeExpression (Required (Null PGfloat8)) Source #
double precision floating-point number (8 bytes)
serial2 :: TypeExpression (Optional (NotNull PGint2)) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type `PGint2
smallserial :: TypeExpression (Optional (NotNull PGint2)) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type `PGint2
serial4 :: TypeExpression (Optional (NotNull PGint4)) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type `PGint4
serial :: TypeExpression (Optional (NotNull PGint4)) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type `PGint4
serial8 :: TypeExpression (Optional (NotNull PGint8)) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type `PGint8
bigserial :: TypeExpression (Optional (NotNull PGint8)) Source #
not a true type, but merely a notational convenience for creating
unique identifier columns with type `PGint8
char :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression (Required (Null (PGchar n))) Source #
fixed-length character string
character :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression (Required (Null (PGchar n))) Source #
fixed-length character string
varchar :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression (Required (Null (PGvarchar n))) Source #
variable-length character string
characterVarying :: (KnownNat n, 1 <= n) => proxy n -> TypeExpression (Required (Null (PGvarchar n))) Source #
variable-length character string
timestamp :: TypeExpression (Required (Null PGtimestamp)) Source #
date and time (no time zone)
timestampWithTimeZone :: TypeExpression (Required (Null PGtimestamptz)) Source #
date and time, including time zone
timeWithTimeZone :: TypeExpression (Required (Null PGtimetz)) Source #
time of day, including time zone
interval :: TypeExpression (Required (Null PGinterval)) Source #
time span
notNull :: TypeExpression (optionality (Null ty)) -> TypeExpression (optionality (NotNull ty)) Source #
used in createTable
commands as a column constraint to ensure
NULL
is not present
default_ :: Expression '[] Ungrouped '[] (Required ty) -> TypeExpression (Required ty) -> TypeExpression (Optional ty) Source #
used in createTable
commands as a column constraint to give a default
Re-export
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
, 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.K
a
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 ]
Instances
HTrans k1 [k1] k2 [k2] (NP k1) (NP k2) | |
HPure k [k] (NP k) | |
HAp k [k] (NP k) | |
HCollapse k [k] (NP k) | |
HSequence k [k] (NP k) | |
All k (Compose * k Eq f) xs => Eq (NP k f xs) | |
(All k (Compose * k Eq f) xs, All k (Compose * k Ord f) xs) => Ord (NP k f xs) | |
All k (Compose * k Show f) xs => Show (NP k f xs) | |
All k (Compose * k NFData f) xs => NFData (NP k f xs) | Since: 0.2.5.0 |
type AllZipN k [k] a b [a] [b] (NP k) c | |
type Same k1 [k1] k2 [k2] (NP k1) | |
type Prod k [k] (NP k) | |
type UnProd k [k] (NP k) | |
type SListIN k [k] (NP k) | |
type CollapseTo k [k] (NP k) a | |
type AllN k [k] (NP k) c | |