squeal-postgresql-0.5.2.0: Squeal PostgreSQL Library

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

Squeal.PostgreSQL.Expression.Aggregate

Description

Aggregate functions

Synopsis

Documentation

class Aggregate expr1 exprN aggr | aggr -> expr1, aggr -> exprN where Source #

Aggregate functions compute a single result from a set of input values. Aggregate functions can be used as GroupedBy Expressions as well as WindowFunctions.

Methods

countStar :: aggr (NotNull PGint8) Source #

A special aggregation that does not require an input

>>> :{
let
  expression :: Expression '[] commons ('Grouped bys) schemas params from ('NotNull 'PGint8)
  expression = countStar
in printSQL expression
:}
count(*)

count Source #

Arguments

:: expr1 ty

what to count

-> aggr (NotNull PGint8) 
>>> :{
let
  expression :: Expression '[] commons ('Grouped bys) schemas params '[tab ::: '["col" ::: null ty]] ('NotNull 'PGint8)
  expression = count (All #col)
in printSQL expression
:}
count(ALL "col")

sum_ :: expr1 (null ty) -> aggr (Null (PGSum ty)) Source #

>>> :{
let
  expression :: Expression '[] commons ('Grouped bys) schemas params '[tab ::: '["col" ::: 'Null 'PGnumeric]] ('Null 'PGnumeric)
  expression = sum_ (Distinct #col)
in printSQL expression
:}
sum(DISTINCT "col")

arrayAgg :: expr1 ty -> aggr (Null (PGvararray ty)) Source #

input values, including nulls, concatenated into an array

jsonAgg :: expr1 ty -> aggr (Null PGjson) Source #

aggregates values as a JSON array

jsonbAgg :: expr1 ty -> aggr (Null PGjsonb) Source #

aggregates values as a JSON array

bitAnd Source #

Arguments

:: int `In` PGIntegral 
=> expr1 (null int)

what to aggregate

-> aggr (Null int) 

the bitwise AND of all non-null input values, or null if none

>>> :{
let
  expression :: Expression '[] commons ('Grouped bys) schemas params '[tab ::: '["col" ::: null 'PGint4]] ('Null 'PGint4)
  expression = bitAnd (Distinct #col)
in printSQL expression
:}
bit_and(DISTINCT "col")

bitOr Source #

Arguments

:: int `In` PGIntegral 
=> expr1 (null int)

what to aggregate

-> aggr (Null int) 

the bitwise OR of all non-null input values, or null if none

>>> :{
let
  expression :: Expression '[] commons ('Grouped bys) schemas params '[tab ::: '["col" ::: null 'PGint4]] ('Null 'PGint4)
  expression = bitOr (All #col)
in printSQL expression
:}
bit_or(ALL "col")

boolAnd Source #

Arguments

:: expr1 (null PGbool)

what to aggregate

-> aggr (Null PGbool) 

true if all input values are true, otherwise false

>>> :{
let
  winFun :: WindowFunction '[] commons 'Ungrouped schemas params '[tab ::: '["col" ::: null 'PGbool]] ('Null 'PGbool)
  winFun = boolAnd #col
in printSQL winFun
:}
bool_and("col")

boolOr Source #

Arguments

:: expr1 (null PGbool)

what to aggregate

-> aggr (Null PGbool) 

true if at least one input value is true, otherwise false

>>> :{
let
  expression :: Expression '[] commons ('Grouped bys) schemas params '[tab ::: '["col" ::: null 'PGbool]] ('Null 'PGbool)
  expression = boolOr (All #col)
in printSQL expression
:}
bool_or(ALL "col")

every Source #

Arguments

:: expr1 (null PGbool)

what to aggregate

-> aggr (Null PGbool) 

equivalent to boolAnd

>>> :{
let
  expression :: Expression '[] commons ('Grouped bys) schemas params '[tab ::: '["col" ::: null 'PGbool]] ('Null 'PGbool)
  expression = every (Distinct #col)
in printSQL expression
:}
every(DISTINCT "col")

max_ Source #

Arguments

:: expr1 (null ty)

what to maximize

-> aggr (Null ty) 

maximum value of expression across all input values

min_ Source #

Arguments

:: expr1 (null ty)

what to minimize

-> aggr (Null ty) 

minimum value of expression across all input values

avg Source #

Arguments

:: expr1 (null ty)

what to average

-> aggr (Null (PGAvg ty)) 

the average (arithmetic mean) of all input values

corr :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

correlation coefficient

>>> :{
let
  expression :: Expression '[] c ('Grouped g) s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8)
  expression = corr (All (#y *: #x))
in printSQL expression
:}
corr(ALL "y", "x")

covarPop :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

population covariance

>>> :{
let
  expression :: Expression '[] c ('Grouped g) s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8)
  expression = covarPop (All (#y *: #x))
in printSQL expression
:}
covar_pop(ALL "y", "x")

covarSamp :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

sample covariance

>>> :{
let
  winFun :: WindowFunction '[] c 'Ungrouped s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8)
  winFun = covarSamp (#y *: #x)
in printSQL winFun
:}
covar_samp("y", "x")

regrAvgX :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

average of the independent variable (sum(X)/N)

>>> :{
let
  expression :: Expression '[] c ('Grouped g) s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8)
  expression = regrAvgX (All (#y *: #x))
in printSQL expression
:}
regr_avgx(ALL "y", "x")

regrAvgY :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

average of the dependent variable (sum(Y)/N)

>>> :{
let
  winFun :: WindowFunction '[] c 'Ungrouped s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8)
  winFun = regrAvgY (#y *: #x)
in printSQL winFun
:}
regr_avgy("y", "x")

regrCount :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGint8) Source #

number of input rows in which both expressions are nonnull

>>> :{
let
  winFun :: WindowFunction '[] c 'Ungrouped s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGint8)
  winFun = regrCount (#y *: #x)
in printSQL winFun
:}
regr_count("y", "x")

regrIntercept :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

y-intercept of the least-squares-fit linear equation determined by the (X, Y) pairs >>> :{ let expression :: Expression '[] c ('Grouped g) s p '[t ::: '["x" ::: 'NotNull 'PGfloat8, "y" ::: 'NotNull 'PGfloat8]] ('Null 'PGfloat8) expression = regrIntercept (All (x)) in printSQL expression :} regr_intercept(ALL "y", "x")

regrR2 :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

regr_r2(Y, X), square of the correlation coefficient

regrSlope :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

regr_slope(Y, X), slope of the least-squares-fit linear equation determined by the (X, Y) pairs

regrSxx :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

regr_sxx(Y, X), sum(X^2) - sum(X)^2/N (“sum of squares” of the independent variable)

regrSxy :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

regr_sxy(Y, X), sum(X*Y) - sum(X) * sum(Y)/N (“sum of products” of independent times dependent variable)

regrSyy :: exprN '[null PGfloat8, null PGfloat8] -> aggr (Null PGfloat8) Source #

regr_syy(Y, X), sum(Y^2) - sum(Y)^2/N (“sum of squares” of the dependent variable)

stddev :: expr1 (null ty) -> aggr (Null (PGAvg ty)) Source #

historical alias for stddevSamp

stddevPop :: expr1 (null ty) -> aggr (Null (PGAvg ty)) Source #

population standard deviation of the input values

stddevSamp :: expr1 (null ty) -> aggr (Null (PGAvg ty)) Source #

sample standard deviation of the input values

variance :: expr1 (null ty) -> aggr (Null (PGAvg ty)) Source #

historical alias for varSamp

varPop :: expr1 (null ty) -> aggr (Null (PGAvg ty)) Source #

population variance of the input values (square of the population standard deviation)

varSamp :: expr1 (null ty) -> aggr (Null (PGAvg ty)) Source #

sample variance of the input values (square of the sample standard deviation)

Instances
Aggregate (Distinction (Expression outer commons Ungrouped schemas params from)) (Distinction (NP (Expression outer commons Ungrouped schemas params from)) :: [NullityType] -> Type) (Expression outer commons (Grouped bys) schemas params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

countStar :: Expression outer commons (Grouped bys) schemas params from (NotNull PGint8) Source #

count :: Distinction (Expression outer commons Ungrouped schemas params from) ty -> Expression outer commons (Grouped bys) schemas params from (NotNull PGint8) Source #

sum_ :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGSum ty)) Source #

arrayAgg :: Distinction (Expression outer commons Ungrouped schemas params from) ty -> Expression outer commons (Grouped bys) schemas params from (Null (PGvararray ty)) Source #

jsonAgg :: Distinction (Expression outer commons Ungrouped schemas params from) ty -> Expression outer commons (Grouped bys) schemas params from (Null PGjson) Source #

jsonbAgg :: Distinction (Expression outer commons Ungrouped schemas params from) ty -> Expression outer commons (Grouped bys) schemas params from (Null PGjsonb) Source #

bitAnd :: In int PGIntegral => Distinction (Expression outer commons Ungrouped schemas params from) (null int) -> Expression outer commons (Grouped bys) schemas params from (Null int) Source #

bitOr :: In int PGIntegral => Distinction (Expression outer commons Ungrouped schemas params from) (null int) -> Expression outer commons (Grouped bys) schemas params from (Null int) Source #

boolAnd :: Distinction (Expression outer commons Ungrouped schemas params from) (null PGbool) -> Expression outer commons (Grouped bys) schemas params from (Null PGbool) Source #

boolOr :: Distinction (Expression outer commons Ungrouped schemas params from) (null PGbool) -> Expression outer commons (Grouped bys) schemas params from (Null PGbool) Source #

every :: Distinction (Expression outer commons Ungrouped schemas params from) (null PGbool) -> Expression outer commons (Grouped bys) schemas params from (Null PGbool) Source #

max_ :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null ty) Source #

min_ :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null ty) Source #

avg :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

corr :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

covarPop :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

covarSamp :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrAvgX :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrAvgY :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrCount :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGint8) Source #

regrIntercept :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrR2 :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrSlope :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrSxx :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrSxy :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrSyy :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

stddev :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

stddevPop :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

stddevSamp :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

variance :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

varPop :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

varSamp :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

Aggregate (Expression outer commons grp schemas params from) (NP (Expression outer commons grp schemas params from) :: [NullityType] -> Type) (WindowFunction outer commons grp schemas params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

countStar :: WindowFunction outer commons grp schemas params from (NotNull PGint8) Source #

count :: Expression outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from (NotNull PGint8) Source #

sum_ :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGSum ty)) Source #

arrayAgg :: Expression outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from (Null (PGvararray ty)) Source #

jsonAgg :: Expression outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from (Null PGjson) Source #

jsonbAgg :: Expression outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from (Null PGjsonb) Source #

bitAnd :: In int PGIntegral => Expression outer commons grp schemas params from (null int) -> WindowFunction outer commons grp schemas params from (Null int) Source #

bitOr :: In int PGIntegral => Expression outer commons grp schemas params from (null int) -> WindowFunction outer commons grp schemas params from (Null int) Source #

boolAnd :: Expression outer commons grp schemas params from (null PGbool) -> WindowFunction outer commons grp schemas params from (Null PGbool) Source #

boolOr :: Expression outer commons grp schemas params from (null PGbool) -> WindowFunction outer commons grp schemas params from (Null PGbool) Source #

every :: Expression outer commons grp schemas params from (null PGbool) -> WindowFunction outer commons grp schemas params from (Null PGbool) Source #

max_ :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null ty) Source #

min_ :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null ty) Source #

avg :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source #

corr :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

covarPop :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

covarSamp :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

regrAvgX :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

regrAvgY :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

regrCount :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGint8) Source #

regrIntercept :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

regrR2 :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

regrSlope :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

regrSxx :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

regrSxy :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

regrSyy :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source #

stddev :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source #

stddevPop :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source #

stddevSamp :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source #

variance :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source #

varPop :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source #

varSamp :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source #

data Distinction (expr :: kind -> Type) (ty :: kind) Source #

Distinctions are used for the input of Aggregate Expressions. All invokes the aggregate once for each input row. Distinct invokes the aggregate once for each distinct value of the expression (or distinct set of values, for multiple expressions) found in the input

Constructors

All (expr ty) 
Distinct (expr ty) 
Instances
Aggregate (Distinction (Expression outer commons Ungrouped schemas params from)) (Distinction (NP (Expression outer commons Ungrouped schemas params from)) :: [NullityType] -> Type) (Expression outer commons (Grouped bys) schemas params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

countStar :: Expression outer commons (Grouped bys) schemas params from (NotNull PGint8) Source #

count :: Distinction (Expression outer commons Ungrouped schemas params from) ty -> Expression outer commons (Grouped bys) schemas params from (NotNull PGint8) Source #

sum_ :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGSum ty)) Source #

arrayAgg :: Distinction (Expression outer commons Ungrouped schemas params from) ty -> Expression outer commons (Grouped bys) schemas params from (Null (PGvararray ty)) Source #

jsonAgg :: Distinction (Expression outer commons Ungrouped schemas params from) ty -> Expression outer commons (Grouped bys) schemas params from (Null PGjson) Source #

jsonbAgg :: Distinction (Expression outer commons Ungrouped schemas params from) ty -> Expression outer commons (Grouped bys) schemas params from (Null PGjsonb) Source #

bitAnd :: In int PGIntegral => Distinction (Expression outer commons Ungrouped schemas params from) (null int) -> Expression outer commons (Grouped bys) schemas params from (Null int) Source #

bitOr :: In int PGIntegral => Distinction (Expression outer commons Ungrouped schemas params from) (null int) -> Expression outer commons (Grouped bys) schemas params from (Null int) Source #

boolAnd :: Distinction (Expression outer commons Ungrouped schemas params from) (null PGbool) -> Expression outer commons (Grouped bys) schemas params from (Null PGbool) Source #

boolOr :: Distinction (Expression outer commons Ungrouped schemas params from) (null PGbool) -> Expression outer commons (Grouped bys) schemas params from (Null PGbool) Source #

every :: Distinction (Expression outer commons Ungrouped schemas params from) (null PGbool) -> Expression outer commons (Grouped bys) schemas params from (Null PGbool) Source #

max_ :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null ty) Source #

min_ :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null ty) Source #

avg :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

corr :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

covarPop :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

covarSamp :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrAvgX :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrAvgY :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrCount :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGint8) Source #

regrIntercept :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrR2 :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrSlope :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrSxx :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrSxy :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

regrSyy :: Distinction (NP (Expression outer commons Ungrouped schemas params from)) (null PGfloat8 ': (null PGfloat8 ': [])) -> Expression outer commons (Grouped bys) schemas params from (Null PGfloat8) Source #

stddev :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

stddevPop :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

stddevSamp :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

variance :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

varPop :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

varSamp :: Distinction (Expression outer commons Ungrouped schemas params from) (null ty) -> Expression outer commons (Grouped bys) schemas params from (Null (PGAvg ty)) Source #

Eq (expr ty) => Eq (Distinction expr ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

(==) :: Distinction expr ty -> Distinction expr ty -> Bool #

(/=) :: Distinction expr ty -> Distinction expr ty -> Bool #

Ord (expr ty) => Ord (Distinction expr ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

compare :: Distinction expr ty -> Distinction expr ty -> Ordering #

(<) :: Distinction expr ty -> Distinction expr ty -> Bool #

(<=) :: Distinction expr ty -> Distinction expr ty -> Bool #

(>) :: Distinction expr ty -> Distinction expr ty -> Bool #

(>=) :: Distinction expr ty -> Distinction expr ty -> Bool #

max :: Distinction expr ty -> Distinction expr ty -> Distinction expr ty #

min :: Distinction expr ty -> Distinction expr ty -> Distinction expr ty #

Show (expr ty) => Show (Distinction expr ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

showsPrec :: Int -> Distinction expr ty -> ShowS #

show :: Distinction expr ty -> String #

showList :: [Distinction expr ty] -> ShowS #

Generic (Distinction expr ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Associated Types

type Rep (Distinction expr ty) :: Type -> Type #

Methods

from :: Distinction expr ty -> Rep (Distinction expr ty) x #

to :: Rep (Distinction expr ty) x -> Distinction expr ty #

NFData (Distinction (Expression outer commons grp schemas params from) ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

rnf :: Distinction (Expression outer commons grp schemas params from) ty -> () #

SListI tys => RenderSQL (Distinction (NP (Expression outer commons grp schemas params from)) tys) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

renderSQL :: Distinction (NP (Expression outer commons grp schemas params from)) tys -> ByteString Source #

RenderSQL (Distinction (Expression outer commons grp schemas params from) ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

Methods

renderSQL :: Distinction (Expression outer commons grp schemas params from) ty -> ByteString Source #

type Rep (Distinction expr ty) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Aggregate

type Rep (Distinction expr ty) = D1 (MetaData "Distinction" "Squeal.PostgreSQL.Expression.Aggregate" "squeal-postgresql-0.5.2.0-4fAomBtpMjd6mRwLthA4w2" False) (C1 (MetaCons "All" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (expr ty))) :+: C1 (MetaCons "Distinct" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (expr ty))))

type family PGSum ty where ... Source #

A type family that calculates PGSumPGType of a given argument PGType.

type family PGAvg ty where ... Source #

A type family that calculates PGAvg type of a PGType.