Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Expression.Aggregate
Description
aggregate functions and arguments
Synopsis
- class Aggregate arg expr | expr -> arg where
- countStar :: expr lat with db params from (NotNull PGint8)
- count :: arg '[ty] lat with db params from -> expr lat with db params from (NotNull PGint8)
- sum_ :: arg '[null ty] lat with db params from -> expr lat with db params from (Null (PGSum ty))
- arrayAgg :: arg '[ty] lat with db params from -> expr lat with db params from (Null (PGvararray ty))
- jsonAgg :: arg '[ty] lat with db params from -> expr lat with db params from (Null PGjson)
- jsonbAgg :: arg '[ty] lat with db params from -> expr lat with db params from (Null PGjsonb)
- bitAnd :: int `In` PGIntegral => arg '[null int] lat with db params from -> expr lat with db params from (Null int)
- bitOr :: int `In` PGIntegral => arg '[null int] lat with db params from -> expr lat with db params from (Null int)
- boolAnd :: arg '[null PGbool] lat with db params from -> expr lat with db params from (Null PGbool)
- boolOr :: arg '[null PGbool] lat with db params from -> expr lat with db params from (Null PGbool)
- every :: arg '[null PGbool] lat with db params from -> expr lat with db params from (Null PGbool)
- max_ :: arg '[null ty] lat with db params from -> expr lat with db params from (Null ty)
- min_ :: arg '[null ty] lat with db params from -> expr lat with db params from (Null ty)
- avg :: arg '[null ty] lat with db params from -> expr lat with db params from (Null (PGAvg ty))
- corr :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- covarPop :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- covarSamp :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- regrAvgX :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- regrAvgY :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- regrCount :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGint8)
- regrIntercept :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- regrR2 :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- regrSlope :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- regrSxx :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- regrSxy :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- regrSyy :: arg '[null PGfloat8, null PGfloat8] lat with db params from -> expr lat with db params from (Null PGfloat8)
- stddev :: arg '[null ty] lat with db params from -> expr lat with db params from (Null (PGAvg ty))
- stddevPop :: arg '[null ty] lat with db params from -> expr lat with db params from (Null (PGAvg ty))
- stddevSamp :: arg '[null ty] lat with db params from -> expr lat with db params from (Null (PGAvg ty))
- variance :: arg '[null ty] lat with db params from -> expr lat with db params from (Null (PGAvg ty))
- varPop :: arg '[null ty] lat with db params from -> expr lat with db params from (Null (PGAvg ty))
- varSamp :: arg '[null ty] lat with db params from -> expr lat with db params from (Null (PGAvg ty))
- data AggregateArg (xs :: [NullType]) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType)
- = AggregateAll {
- aggregateArgs :: NP (Expression Ungrouped lat with db params from) xs
- aggregateOrder :: [SortExpression Ungrouped lat with db params from]
- aggregateFilter :: [Condition Ungrouped lat with db params from]
- | AggregateDistinct {
- aggregateArgs :: NP (Expression Ungrouped lat with db params from) xs
- aggregateOrder :: [SortExpression Ungrouped lat with db params from]
- aggregateFilter :: [Condition Ungrouped lat with db params from]
- = AggregateAll {
- pattern All :: Expression Ungrouped lat with db params from x -> AggregateArg '[x] lat with db params from
- pattern Alls :: NP (Expression Ungrouped lat with db params from) xs -> AggregateArg xs lat with db params from
- allNotNull :: Expression Ungrouped lat with db params from (Null x) -> AggregateArg '[NotNull x] lat with db params from
- pattern Distinct :: Expression Ungrouped lat with db params from x -> AggregateArg '[x] lat with db params from
- pattern Distincts :: NP (Expression Ungrouped lat with db params from) xs -> AggregateArg xs lat with db params from
- distinctNotNull :: Expression Ungrouped lat with db params from (Null x) -> AggregateArg '[NotNull x] lat with db params from
- class FilterWhere arg grp | arg -> grp where
- filterWhere :: Condition grp lat with db params from -> arg xs lat with db params from -> arg xs lat with db params from
- type family PGSum ty where ...
- type family PGAvg ty where ...
Aggregate
class Aggregate arg expr | expr -> arg where Source #
Aggregate
functions compute a single result from a set of input values.
Aggregate
functions can be used as Grouped
Expression
s as well
as WindowFunction
s.
Methods
countStar :: expr lat with db params from (NotNull PGint8) Source #
A special aggregation that does not require an input
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params from ('NotNull 'PGint8) expression = countStar in printSQL expression :} count(*)
Arguments
:: arg '[ty] lat with db params from | argument |
-> expr lat with db params from (NotNull PGint8) |
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params '[tab ::: '["col" ::: null ty]] ('NotNull 'PGint8) expression = count (All #col) in printSQL expression :} count(ALL "col")
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGSum ty)) |
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params '[tab ::: '["col" ::: 'Null 'PGnumeric]] ('Null 'PGnumeric) expression = sum_ (Distinct #col & filterWhere (#col .< 100)) in printSQL expression :} sum(DISTINCT "col") FILTER (WHERE ("col" < (100.0 :: numeric)))
Arguments
:: arg '[ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGvararray ty)) |
input values, including nulls, concatenated into an array
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params '[tab ::: '["col" ::: 'Null 'PGnumeric]] ('Null ('PGvararray ('Null 'PGnumeric))) expression = arrayAgg (All #col & orderBy [AscNullsFirst #col] & filterWhere (#col .< 100)) in printSQL expression :} array_agg(ALL "col" ORDER BY "col" ASC NULLS FIRST) FILTER (WHERE ("col" < (100.0 :: numeric)))
aggregates values as a JSON array
aggregates values as a JSON array
Arguments
:: int `In` PGIntegral | |
=> arg '[null int] lat with db params from | argument |
-> expr lat with db params from (Null int) |
the bitwise AND of all non-null input values, or null if none
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params '[tab ::: '["col" ::: null 'PGint4]] ('Null 'PGint4) expression = bitAnd (Distinct #col) in printSQL expression :} bit_and(DISTINCT "col")
Arguments
:: int `In` PGIntegral | |
=> arg '[null int] lat with db params from | argument |
-> expr lat with db params from (Null int) |
the bitwise OR of all non-null input values, or null if none
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params '[tab ::: '["col" ::: null 'PGint4]] ('Null 'PGint4) expression = bitOr (All #col) in printSQL expression :} bit_or(ALL "col")
Arguments
:: arg '[null PGbool] lat with db params from | argument |
-> expr lat with db params from (Null PGbool) |
true if all input values are true, otherwise false
>>>
:{
let winFun :: WindowFunction 'Ungrouped '[] with db params '[tab ::: '["col" ::: null 'PGbool]] ('Null 'PGbool) winFun = boolAnd (Window #col) in printSQL winFun :} bool_and("col")
Arguments
:: arg '[null PGbool] lat with db params from | argument |
-> expr lat with db params from (Null PGbool) |
true if at least one input value is true, otherwise false
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params '[tab ::: '["col" ::: null 'PGbool]] ('Null 'PGbool) expression = boolOr (All #col) in printSQL expression :} bool_or(ALL "col")
Arguments
:: arg '[null PGbool] lat with db params from | argument |
-> expr lat with db params from (Null PGbool) |
equivalent to boolAnd
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params '[tab ::: '["col" ::: null 'PGbool]] ('Null 'PGbool) expression = every (Distinct #col) in printSQL expression :} every(DISTINCT "col")
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null ty) |
maximum value of expression across all input values
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null ty) |
minimum value of expression across all input values
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGAvg ty)) |
the average (arithmetic mean) of all input values
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
correlation coefficient
>>>
:{
let expression :: Expression ('Grouped g) '[] c s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8) expression = corr (Alls (#y *: #x)) in printSQL expression :} corr(ALL "y", "x")
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
population covariance
>>>
:{
let expression :: Expression ('Grouped g) '[] c s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8) expression = covarPop (Alls (#y *: #x)) in printSQL expression :} covar_pop(ALL "y", "x")
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
sample covariance
>>>
:{
let winFun :: WindowFunction 'Ungrouped '[] c s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8) winFun = covarSamp (Windows (#y *: #x)) in printSQL winFun :} covar_samp("y", "x")
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
average of the independent variable (sum(X)/N)
>>>
:{
let expression :: Expression ('Grouped g) '[] c s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8) expression = regrAvgX (Alls (#y *: #x)) in printSQL expression :} regr_avgx(ALL "y", "x")
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
average of the dependent variable (sum(Y)/N)
>>>
:{
let winFun :: WindowFunction 'Ungrouped '[] c s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8) winFun = regrAvgY (Windows (#y *: #x)) in printSQL winFun :} regr_avgy("y", "x")
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGint8) |
number of input rows in which both expressions are nonnull
>>>
:{
let winFun :: WindowFunction 'Ungrouped '[] c s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGint8) winFun = regrCount (Windows (#y *: #x)) in printSQL winFun :} regr_count("y", "x")
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
y-intercept of the least-squares-fit linear equation determined by the (X, Y) pairs
>>>
:{
let expression :: Expression ('Grouped g) '[] c s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8) expression = regrIntercept (Alls (#y *: #x)) in printSQL expression :} regr_intercept(ALL "y", "x")
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
regr_r2(Y, X)
, square of the correlation coefficient
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
regr_slope(Y, X)
, slope of the least-squares-fit linear equation
determined by the (X, Y) pairs
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
regr_sxx(Y, X)
, sum(X^2) - sum(X)^2/N
(“sum of squares” of the independent variable)
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
regr_sxy(Y, X)
, sum(X*Y) - sum(X) * sum(Y)/N
(“sum of products” of independent times dependent variable)
Arguments
:: arg '[null PGfloat8, null PGfloat8] lat with db params from | arguments |
-> expr lat with db params from (Null PGfloat8) |
regr_syy(Y, X)
, sum(Y^2) - sum(Y)^2/N
(“sum of squares” of the dependent variable)
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGAvg ty)) |
historical alias for stddevSamp
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGAvg ty)) |
population standard deviation of the input values
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGAvg ty)) |
sample standard deviation of the input values
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGAvg ty)) |
historical alias for varSamp
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGAvg ty)) |
population variance of the input values (square of the population standard deviation)
Arguments
:: arg '[null ty] lat with db params from | argument |
-> expr lat with db params from (Null (PGAvg ty)) |
sample variance of the input values (square of the sample standard deviation)
Instances
Aggregate AggregateArg (Expression (Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate Methods countStar :: Expression (Grouped bys) lat with db params from (NotNull PGint8) Source # count :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (NotNull PGint8) Source # sum_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGSum ty)) Source # arrayAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGvararray ty)) Source # jsonAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGjson) Source # jsonbAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGjsonb) Source # bitAnd :: In int PGIntegral => AggregateArg (null int ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null int) Source # bitOr :: In int PGIntegral => AggregateArg (null int ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null int) Source # boolAnd :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # boolOr :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # every :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # max_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null ty) Source # min_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null ty) Source # avg :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # corr :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # covarPop :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # covarSamp :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrAvgX :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrAvgY :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrCount :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGint8) Source # regrIntercept :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrR2 :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSlope :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSxx :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSxy :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSyy :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # stddev :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # stddevPop :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # stddevSamp :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # variance :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # varPop :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # varSamp :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # | |
Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods countStar :: WindowFunction grp lat with db params from (NotNull PGint8) Source # count :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (NotNull PGint8) Source # sum_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGSum ty)) Source # arrayAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGvararray ty)) Source # jsonAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGjson) Source # jsonbAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGjsonb) Source # bitAnd :: In int PGIntegral => WindowArg grp (null int ': []) lat with db params from -> WindowFunction grp lat with db params from (Null int) Source # bitOr :: In int PGIntegral => WindowArg grp (null int ': []) lat with db params from -> WindowFunction grp lat with db params from (Null int) Source # boolAnd :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # boolOr :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # every :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # max_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null ty) Source # min_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null ty) Source # avg :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # corr :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # covarPop :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # covarSamp :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrAvgX :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrAvgY :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrCount :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGint8) Source # regrIntercept :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrR2 :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSlope :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSxx :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSxy :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSyy :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # stddev :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # stddevPop :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # stddevSamp :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # variance :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # varPop :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # varSamp :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # |
Aggregate Arguments
data AggregateArg (xs :: [NullType]) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) Source #
AggregateArg
s are used for the input of Aggregate
Expression
s.
Constructors
AggregateAll | |
Fields
| |
AggregateDistinct | |
Fields
|
Instances
Aggregate AggregateArg (Expression (Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate Methods countStar :: Expression (Grouped bys) lat with db params from (NotNull PGint8) Source # count :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (NotNull PGint8) Source # sum_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGSum ty)) Source # arrayAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGvararray ty)) Source # jsonAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGjson) Source # jsonbAgg :: AggregateArg (ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGjsonb) Source # bitAnd :: In int PGIntegral => AggregateArg (null int ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null int) Source # bitOr :: In int PGIntegral => AggregateArg (null int ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null int) Source # boolAnd :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # boolOr :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # every :: AggregateArg (null PGbool ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGbool) Source # max_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null ty) Source # min_ :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null ty) Source # avg :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # corr :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # covarPop :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # covarSamp :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrAvgX :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrAvgY :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrCount :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGint8) Source # regrIntercept :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrR2 :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSlope :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSxx :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSxy :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # regrSyy :: AggregateArg (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> Expression (Grouped bys) lat with db params from (Null PGfloat8) Source # stddev :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # stddevPop :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # stddevSamp :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # variance :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # varPop :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # varSamp :: AggregateArg (null ty ': []) lat with db params from -> Expression (Grouped bys) lat with db params from (Null (PGAvg ty)) Source # | |
OrderBy (AggregateArg xs) Ungrouped Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate Methods orderBy :: [SortExpression Ungrouped lat with db params from] -> AggregateArg xs lat with db params from -> AggregateArg xs lat with db params from Source # | |
FilterWhere AggregateArg Ungrouped Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate Methods filterWhere :: Condition Ungrouped lat with db params from -> AggregateArg xs lat with db params from -> AggregateArg xs lat with db params from Source # | |
SListI xs => RenderSQL (AggregateArg xs lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate Methods renderSQL :: AggregateArg xs lat with db params from -> ByteString Source # |
Arguments
:: Expression Ungrouped lat with db params from x | argument |
-> AggregateArg '[x] lat with db params from |
All
invokes the aggregate on a single
argument once for each input row.
Arguments
:: NP (Expression Ungrouped lat with db params from) xs | arguments |
-> AggregateArg xs lat with db params from |
All
invokes the aggregate on multiple
arguments once for each input row.
Arguments
:: Expression Ungrouped lat with db params from (Null x) | argument |
-> AggregateArg '[NotNull x] lat with db params from |
allNotNull
invokes the aggregate on a single
argument once for each input row where the argument
is not null
Arguments
:: Expression Ungrouped lat with db params from x | argument |
-> AggregateArg '[x] lat with db params from |
Distinct
invokes the aggregate once for each
distinct value of the expression found in the input.
Arguments
:: NP (Expression Ungrouped lat with db params from) xs | arguments |
-> AggregateArg xs lat with db params from |
Distincts
invokes the aggregate once for each
distinct set of values, for multiple expressions, found in the input.
Arguments
:: Expression Ungrouped lat with db params from (Null x) | argument |
-> AggregateArg '[NotNull x] lat with db params from |
distinctNotNull
invokes the aggregate once for each
distinct, not null value of the expression found in the input.
class FilterWhere arg grp | arg -> grp where Source #
Permits filtering
WindowArg
s and AggregateArg
s
Methods
Arguments
:: Condition grp lat with db params from | include rows which evaluate to true |
-> arg xs lat with db params from | |
-> arg xs lat with db params from |
If filterWhere
is specified, then only the input rows for which
the Condition
evaluates to true are fed to the aggregate function;
other rows are discarded.
Instances
FilterWhere AggregateArg Ungrouped Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate Methods filterWhere :: Condition Ungrouped lat with db params from -> AggregateArg xs lat with db params from -> AggregateArg xs lat with db params from Source # | |
FilterWhere (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) grp Source # | |
Defined in Squeal.PostgreSQL.Expression.Window |
Aggregate Types
type family PGSum ty where ... Source #
Equations
PGSum PGint2 = PGint8 | |
PGSum PGint4 = PGint8 | |
PGSum PGint8 = PGnumeric | |
PGSum PGfloat4 = PGfloat4 | |
PGSum PGfloat8 = PGfloat8 | |
PGSum PGnumeric = PGnumeric | |
PGSum PGinterval = PGinterval | |
PGSum PGmoney = PGmoney | |
PGSum pg = TypeError (Text "Squeal type error: Cannot sum with argument type " :<>: ShowType pg) |