Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
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.
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(*)
>>>
:{
let expression :: Expression ('Grouped bys) '[] with db params '[tab ::: '["col" ::: null ty]] ('NotNull 'PGint8) expression = count (All #col) in printSQL expression :} count(ALL "col")
>>>
:{
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)))
:: 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
:: 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")
:: 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")
:: 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")
:: 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")
:: 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")
:: 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
:: 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
the average (arithmetic mean) of all input values
:: 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")
:: 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")
:: 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")
:: 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")
:: 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")
:: 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")
:: 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")
:: 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
:: 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
:: 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)
:: 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)
:: 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)
historical alias for stddevSamp
population standard deviation of the input values
sample standard deviation of the input values
historical alias for varSamp
population variance of the input values (square of the population standard deviation)
sample variance of the input values (square of the sample standard deviation)
Instances
(TypeError ('Text "Cannot use aggregate functions to construct an Ungrouped Expression. Add a 'groupBy' to your TableExpression. If you want to aggregate across the entire result set, use 'groupBy Nil'.") :: Constraint, a ~ AggregateArg) => Aggregate (a :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (Expression 'Ungrouped) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression 'Ungrouped lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => a '[null int] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => a '[null int] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGbool] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). a '[null ty] lat with db params from -> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty)) Source # | |
Aggregate AggregateArg (Expression ('Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). 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 countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowFunction grp lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). 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.
AggregateAll | |
| |
AggregateDistinct | |
|
Instances
Aggregate AggregateArg (Expression ('Grouped bys) :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source # count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('NotNull 'PGint8) Source # sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGSum ty)) Source # arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ('PGvararray ty)) Source # jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjson) Source # jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGjsonb) Source # bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source # bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => AggregateArg '[null int] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null int) Source # boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGbool] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGbool) Source # max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source # min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null ty) Source # avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGint8) Source # regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null 'PGfloat8) Source # stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). AggregateArg '[null ty] lat with db params from -> Expression ('Grouped bys) lat with db params from ('Null (PGAvg ty)) Source # | |
(Has tab (Join from lat) row, Has col row ty) => IsQualified tab col (AggregateArg '[ty] lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate | |
(HasUnique tab (Join from lat) row, Has col row ty) => IsLabel col (AggregateArg '[ty] lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate fromLabel :: AggregateArg '[ty] lat with db params from # | |
OrderBy (AggregateArg xs) 'Ungrouped Source # | |
Defined in Squeal.PostgreSQL.Expression.Aggregate orderBy :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). [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 filterWhere :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (xs :: k). 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 renderSQL :: AggregateArg xs lat with db params from -> ByteString Source # |
:: 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.
:: 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.
:: 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
:: 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.
:: 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.
:: 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
:: 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 filterWhere :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (xs :: k). 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 #
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) |