{-# LANGUAGE
DataKinds
, DeriveGeneric
, FlexibleContexts
, FlexibleInstances
, FunctionalDependencies
, LambdaCase
, MultiParamTypeClasses
, OverloadedStrings
, PatternSynonyms
, PolyKinds
, ScopedTypeVariables
, StandaloneDeriving
, TypeApplications
, TypeFamilies
, TypeOperators
, UndecidableInstances
#-}
module Squeal.PostgreSQL.Expression.Aggregate
(
Aggregate (..)
, AggregateArg (..)
, pattern All
, pattern Alls
, allNotNull
, pattern Distinct
, pattern Distincts
, distinctNotNull
, FilterWhere (..)
, PGSum
, PGAvg
) where
import Data.ByteString (ByteString)
import GHC.TypeLits
import qualified Generics.SOP as SOP
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.Logic
import Squeal.PostgreSQL.Expression.Null
import Squeal.PostgreSQL.Expression.Sort
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
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
{ AggregateArg xs lat with db params from
-> NP (Expression 'Ungrouped lat with db params from) xs
aggregateArgs :: NP (Expression 'Ungrouped lat with db params from) xs
, AggregateArg xs lat with db params from
-> [SortExpression 'Ungrouped lat with db params from]
aggregateOrder :: [SortExpression 'Ungrouped lat with db params from]
, AggregateArg xs lat with db params from
-> [Condition '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]
}
instance (HasUnique tab (Join from lat) row, Has col row ty)
=> IsLabel col (AggregateArg '[ty] lat with db params from) where
fromLabel :: AggregateArg '[ty] lat with db params from
fromLabel = Expression 'Ungrouped lat with db params from ty
-> AggregateArg '[ty] lat with db params from
forall (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(x :: NullType).
Expression 'Ungrouped lat with db params from x
-> AggregateArg '[x] lat with db params from
All (forall a. IsLabel col a => a
forall (x :: Symbol) a. IsLabel x a => a
fromLabel @col)
instance (Has tab (Join from lat) row, Has col row ty)
=> IsQualified tab col (AggregateArg '[ty] lat with db params from) where
Alias tab
tab ! :: Alias tab
-> Alias col -> AggregateArg '[ty] lat with db params from
! Alias col
col = Expression 'Ungrouped lat with db params from ty
-> AggregateArg '[ty] lat with db params from
forall (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(x :: NullType).
Expression 'Ungrouped lat with db params from x
-> AggregateArg '[x] lat with db params from
All (Alias tab
tab Alias tab
-> Alias col -> Expression 'Ungrouped lat with db params from ty
forall (qualifier :: Symbol) (alias :: Symbol) expression.
IsQualified qualifier alias expression =>
Alias qualifier -> Alias alias -> expression
! Alias col
col)
instance SOP.SListI xs => RenderSQL (AggregateArg xs lat with db params from) where
renderSQL :: AggregateArg xs lat with db params from -> ByteString
renderSQL = \case
AggregateAll NP (Expression 'Ungrouped lat with db params from) xs
args [SortExpression 'Ungrouped lat with db params from]
sorts [Condition 'Ungrouped lat with db params from]
filters ->
ByteString -> ByteString
parenthesized
(ByteString
"ALL" ByteString -> ByteString -> ByteString
<+> (forall (x :: NullType).
Expression 'Ungrouped lat with db params from x -> ByteString)
-> NP (Expression 'Ungrouped lat with db params from) xs
-> ByteString
forall k (xs :: [k]) (expression :: k -> *).
SListI xs =>
(forall (x :: k). expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparated forall sql. RenderSQL sql => sql -> ByteString
forall (x :: NullType).
Expression 'Ungrouped lat with db params from x -> ByteString
renderSQL NP (Expression 'Ungrouped lat with db params from) xs
argsByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> [SortExpression 'Ungrouped lat with db params from] -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL [SortExpression 'Ungrouped lat with db params from]
sorts)
ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> [Condition 'Ungrouped lat with db params from] -> ByteString
forall (grp :: Grouping) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(null :: PGType -> NullType).
[Expression grp lat with db params from (null 'PGbool)]
-> ByteString
renderFilters [Condition 'Ungrouped lat with db params from]
filters
AggregateDistinct NP (Expression 'Ungrouped lat with db params from) xs
args [SortExpression 'Ungrouped lat with db params from]
sorts [Condition 'Ungrouped lat with db params from]
filters ->
ByteString -> ByteString
parenthesized
(ByteString
"DISTINCT" ByteString -> ByteString -> ByteString
<+> (forall (x :: NullType).
Expression 'Ungrouped lat with db params from x -> ByteString)
-> NP (Expression 'Ungrouped lat with db params from) xs
-> ByteString
forall k (xs :: [k]) (expression :: k -> *).
SListI xs =>
(forall (x :: k). expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparated forall sql. RenderSQL sql => sql -> ByteString
forall (x :: NullType).
Expression 'Ungrouped lat with db params from x -> ByteString
renderSQL NP (Expression 'Ungrouped lat with db params from) xs
args ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> [SortExpression 'Ungrouped lat with db params from] -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL [SortExpression 'Ungrouped lat with db params from]
sorts)
ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> [Condition 'Ungrouped lat with db params from] -> ByteString
forall (grp :: Grouping) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(null :: PGType -> NullType).
[Expression grp lat with db params from (null 'PGbool)]
-> ByteString
renderFilters [Condition 'Ungrouped lat with db params from]
filters
where
renderFilter :: ByteString -> ByteString
renderFilter ByteString
wh = ByteString
"FILTER" ByteString -> ByteString -> ByteString
<+> ByteString -> ByteString
parenthesized (ByteString
"WHERE" ByteString -> ByteString -> ByteString
<+> ByteString
wh)
renderFilters :: [Expression grp lat with db params from (null 'PGbool)]
-> ByteString
renderFilters = \case
[] -> ByteString
""
Expression grp lat with db params from (null 'PGbool)
wh:[Expression grp lat with db params from (null 'PGbool)]
whs -> ByteString
" " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
renderFilter (Expression grp lat with db params from (null 'PGbool) -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL ((Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool))
-> Expression grp lat with db params from (null 'PGbool)
-> [Expression grp lat with db params from (null 'PGbool)]
-> Expression grp lat with db params from (null 'PGbool)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool)
-> Expression grp lat with db params from (null 'PGbool)
forall (null :: PGType -> NullType).
Operator (null 'PGbool) (null 'PGbool) (null 'PGbool)
(.&&) Expression grp lat with db params from (null 'PGbool)
wh [Expression grp lat with db params from (null 'PGbool)]
whs))
instance OrderBy (AggregateArg xs) 'Ungrouped where
orderBy :: [SortExpression 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
-> AggregateArg xs lat with db params from
orderBy [SortExpression 'Ungrouped lat with db params from]
sorts1 = \case
AggregateAll NP (Expression 'Ungrouped lat with db params from) xs
xs [SortExpression 'Ungrouped lat with db params from]
sorts0 [Condition 'Ungrouped lat with db params from]
whs -> NP (Expression 'Ungrouped lat with db params from) xs
-> [SortExpression 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])]).
NP (Expression 'Ungrouped lat with db params from) xs
-> [SortExpression 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
AggregateAll NP (Expression 'Ungrouped lat with db params from) xs
xs ([SortExpression 'Ungrouped lat with db params from]
sorts0 [SortExpression 'Ungrouped lat with db params from]
-> [SortExpression 'Ungrouped lat with db params from]
-> [SortExpression 'Ungrouped lat with db params from]
forall a. [a] -> [a] -> [a]
++ [SortExpression 'Ungrouped lat with db params from]
sorts1) [Condition 'Ungrouped lat with db params from]
whs
AggregateDistinct NP (Expression 'Ungrouped lat with db params from) xs
xs [SortExpression 'Ungrouped lat with db params from]
sorts0 [Condition 'Ungrouped lat with db params from]
whs -> NP (Expression 'Ungrouped lat with db params from) xs
-> [SortExpression 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])]).
NP (Expression 'Ungrouped lat with db params from) xs
-> [SortExpression 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
AggregateDistinct NP (Expression 'Ungrouped lat with db params from) xs
xs ([SortExpression 'Ungrouped lat with db params from]
sorts0 [SortExpression 'Ungrouped lat with db params from]
-> [SortExpression 'Ungrouped lat with db params from]
-> [SortExpression 'Ungrouped lat with db params from]
forall a. [a] -> [a] -> [a]
++ [SortExpression 'Ungrouped lat with db params from]
sorts1) [Condition 'Ungrouped lat with db params from]
whs
pattern All
:: Expression 'Ungrouped lat with db params from x
-> AggregateArg '[x] lat with db params from
pattern $bAll :: Expression 'Ungrouped lat with db params from x
-> AggregateArg '[x] lat with db params from
$mAll :: forall r (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(x :: NullType).
AggregateArg '[x] lat with db params from
-> (Expression 'Ungrouped lat with db params from x -> r)
-> (Void# -> r)
-> r
All x = Alls (x :* Nil)
pattern Alls
:: NP (Expression 'Ungrouped lat with db params from) xs
-> AggregateArg xs lat with db params from
pattern $bAlls :: NP (Expression 'Ungrouped lat with db params from) xs
-> AggregateArg xs lat with db params from
$mAlls :: forall r (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(xs :: [NullType]).
AggregateArg xs lat with db params from
-> (NP (Expression 'Ungrouped lat with db params from) xs -> r)
-> (Void# -> r)
-> r
Alls xs = AggregateAll xs [] []
allNotNull
:: Expression 'Ungrouped lat with db params from ('Null x)
-> AggregateArg '[ 'NotNull x] lat with db params from
allNotNull :: Expression 'Ungrouped lat with db params from ('Null x)
-> AggregateArg '[ 'NotNull x] lat with db params from
allNotNull Expression 'Ungrouped lat with db params from ('Null x)
x = Expression 'Ungrouped lat with db params from ('NotNull x)
-> AggregateArg '[ 'NotNull x] lat with db params from
forall (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(x :: NullType).
Expression 'Ungrouped lat with db params from x
-> AggregateArg '[x] lat with db params from
All (Expression 'Ungrouped lat with db params from ('Null x)
-> Expression 'Ungrouped lat with db params from ('NotNull x)
forall (ty :: PGType). 'Null ty --> 'NotNull ty
unsafeNotNull Expression 'Ungrouped lat with db params from ('Null x)
x) AggregateArg '[ 'NotNull x] lat with db params from
-> (AggregateArg '[ 'NotNull x] lat with db params from
-> AggregateArg '[ 'NotNull x] lat with db params from)
-> AggregateArg '[ 'NotNull x] lat with db params from
forall a b. a -> (a -> b) -> b
& Condition 'Ungrouped lat with db params from
-> AggregateArg '[ 'NotNull x] lat with db params from
-> AggregateArg '[ 'NotNull x] lat with db params from
forall k
(arg :: k
-> [(Symbol, [(Symbol, NullType)])]
-> [(Symbol, [(Symbol, NullType)])]
-> SchemasType
-> [NullType]
-> [(Symbol, [(Symbol, NullType)])]
-> *)
(grp :: Grouping) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(xs :: k).
FilterWhere arg grp =>
Condition grp lat with db params from
-> arg xs lat with db params from -> arg xs lat with db params from
filterWhere (Condition 'Ungrouped lat with db params from
-> Condition 'Ungrouped lat with db params from
forall (null :: PGType -> NullType). null 'PGbool --> null 'PGbool
not_ (Expression 'Ungrouped lat with db params from ('Null x)
-> Condition 'Ungrouped lat with db params from
forall (ty :: PGType) (null :: PGType -> NullType).
'Null ty --> null 'PGbool
isNull Expression 'Ungrouped lat with db params from ('Null x)
x))
pattern Distinct
:: Expression 'Ungrouped lat with db params from x
-> AggregateArg '[x] lat with db params from
pattern $bDistinct :: Expression 'Ungrouped lat with db params from x
-> AggregateArg '[x] lat with db params from
$mDistinct :: forall r (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(x :: NullType).
AggregateArg '[x] lat with db params from
-> (Expression 'Ungrouped lat with db params from x -> r)
-> (Void# -> r)
-> r
Distinct x = Distincts (x :* Nil)
pattern Distincts
:: NP (Expression 'Ungrouped lat with db params from) xs
-> AggregateArg xs lat with db params from
pattern $bDistincts :: NP (Expression 'Ungrouped lat with db params from) xs
-> AggregateArg xs lat with db params from
$mDistincts :: forall r (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(xs :: [NullType]).
AggregateArg xs lat with db params from
-> (NP (Expression 'Ungrouped lat with db params from) xs -> r)
-> (Void# -> r)
-> r
Distincts xs = AggregateDistinct xs [] []
distinctNotNull
:: Expression 'Ungrouped lat with db params from ('Null x)
-> AggregateArg '[ 'NotNull x] lat with db params from
distinctNotNull :: Expression 'Ungrouped lat with db params from ('Null x)
-> AggregateArg '[ 'NotNull x] lat with db params from
distinctNotNull Expression 'Ungrouped lat with db params from ('Null x)
x = Expression 'Ungrouped lat with db params from ('NotNull x)
-> AggregateArg '[ 'NotNull x] lat with db params from
forall (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(x :: NullType).
Expression 'Ungrouped lat with db params from x
-> AggregateArg '[x] lat with db params from
Distinct (Expression 'Ungrouped lat with db params from ('Null x)
-> Expression 'Ungrouped lat with db params from ('NotNull x)
forall (ty :: PGType). 'Null ty --> 'NotNull ty
unsafeNotNull Expression 'Ungrouped lat with db params from ('Null x)
x) AggregateArg '[ 'NotNull x] lat with db params from
-> (AggregateArg '[ 'NotNull x] lat with db params from
-> AggregateArg '[ 'NotNull x] lat with db params from)
-> AggregateArg '[ 'NotNull x] lat with db params from
forall a b. a -> (a -> b) -> b
& Condition 'Ungrouped lat with db params from
-> AggregateArg '[ 'NotNull x] lat with db params from
-> AggregateArg '[ 'NotNull x] lat with db params from
forall k
(arg :: k
-> [(Symbol, [(Symbol, NullType)])]
-> [(Symbol, [(Symbol, NullType)])]
-> SchemasType
-> [NullType]
-> [(Symbol, [(Symbol, NullType)])]
-> *)
(grp :: Grouping) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(xs :: k).
FilterWhere arg grp =>
Condition grp lat with db params from
-> arg xs lat with db params from -> arg xs lat with db params from
filterWhere (Condition 'Ungrouped lat with db params from
-> Condition 'Ungrouped lat with db params from
forall (null :: PGType -> NullType). null 'PGbool --> null 'PGbool
not_ (Expression 'Ungrouped lat with db params from ('Null x)
-> Condition 'Ungrouped lat with db params from
forall (ty :: PGType) (null :: PGType -> NullType).
'Null ty --> null 'PGbool
isNull Expression 'Ungrouped lat with db params from ('Null x)
x))
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
instance FilterWhere AggregateArg 'Ungrouped where
filterWhere :: Condition 'Ungrouped lat with db params from
-> AggregateArg xs lat with db params from
-> AggregateArg xs lat with db params from
filterWhere Condition 'Ungrouped lat with db params from
wh = \case
AggregateAll NP (Expression 'Ungrouped lat with db params from) xs
xs [SortExpression 'Ungrouped lat with db params from]
sorts [Condition 'Ungrouped lat with db params from]
whs -> NP (Expression 'Ungrouped lat with db params from) xs
-> [SortExpression 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])]).
NP (Expression 'Ungrouped lat with db params from) xs
-> [SortExpression 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
AggregateAll NP (Expression 'Ungrouped lat with db params from) xs
xs [SortExpression 'Ungrouped lat with db params from]
sorts (Condition 'Ungrouped lat with db params from
wh Condition 'Ungrouped lat with db params from
-> [Condition 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
forall a. a -> [a] -> [a]
: [Condition 'Ungrouped lat with db params from]
whs)
AggregateDistinct NP (Expression 'Ungrouped lat with db params from) xs
xs [SortExpression 'Ungrouped lat with db params from]
sorts [Condition 'Ungrouped lat with db params from]
whs -> NP (Expression 'Ungrouped lat with db params from) xs
-> [SortExpression 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])]).
NP (Expression 'Ungrouped lat with db params from) xs
-> [SortExpression 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
-> AggregateArg xs lat with db params from
AggregateDistinct NP (Expression 'Ungrouped lat with db params from) xs
xs [SortExpression 'Ungrouped lat with db params from]
sorts (Condition 'Ungrouped lat with db params from
wh Condition 'Ungrouped lat with db params from
-> [Condition 'Ungrouped lat with db params from]
-> [Condition 'Ungrouped lat with db params from]
forall a. a -> [a] -> [a]
: [Condition 'Ungrouped lat with db params from]
whs)
instance Aggregate AggregateArg (Expression ('Grouped bys)) where
countStar :: Expression
('Grouped bys) lat with db params from ('NotNull 'PGint8)
countStar = ByteString
-> Expression
('Grouped bys) lat with db params from ('NotNull 'PGint8)
forall (grp :: Grouping) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression ByteString
"count(*)"
count :: AggregateArg '[ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('NotNull 'PGint8)
count = ByteString
-> AggregateArg '[ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('NotNull 'PGint8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"count"
sum_ :: AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGSum ty))
sum_ = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGSum ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"sum"
arrayAgg :: AggregateArg '[ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null ('PGvararray ty))
arrayAgg = ByteString
-> AggregateArg '[ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null ('PGvararray ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"array_agg"
jsonAgg :: AggregateArg '[ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGjson)
jsonAgg = ByteString
-> AggregateArg '[ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGjson)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"json_agg"
jsonbAgg :: AggregateArg '[ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGjsonb)
jsonbAgg = ByteString
-> AggregateArg '[ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGjsonb)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"jsonb_agg"
bitAnd :: AggregateArg '[null int] lat with db params from
-> Expression ('Grouped bys) lat with db params from ('Null int)
bitAnd = ByteString
-> AggregateArg '[null int] lat with db params from
-> Expression ('Grouped bys) lat with db params from ('Null int)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"bit_and"
bitOr :: AggregateArg '[null int] lat with db params from
-> Expression ('Grouped bys) lat with db params from ('Null int)
bitOr = ByteString
-> AggregateArg '[null int] lat with db params from
-> Expression ('Grouped bys) lat with db params from ('Null int)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"bit_or"
boolAnd :: AggregateArg '[null 'PGbool] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGbool)
boolAnd = ByteString
-> AggregateArg '[null 'PGbool] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGbool)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"bool_and"
boolOr :: AggregateArg '[null 'PGbool] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGbool)
boolOr = ByteString
-> AggregateArg '[null 'PGbool] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGbool)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"bool_or"
every :: AggregateArg '[null 'PGbool] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGbool)
every = ByteString
-> AggregateArg '[null 'PGbool] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGbool)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"every"
max_ :: AggregateArg '[null ty] lat with db params from
-> Expression ('Grouped bys) lat with db params from ('Null ty)
max_ = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression ('Grouped bys) lat with db params from ('Null ty)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"max"
min_ :: AggregateArg '[null ty] lat with db params from
-> Expression ('Grouped bys) lat with db params from ('Null ty)
min_ = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression ('Grouped bys) lat with db params from ('Null ty)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"min"
avg :: AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
avg = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"avg"
corr :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
corr = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"corr"
covarPop :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
covarPop = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"covar_pop"
covarSamp :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
covarSamp = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"covar_samp"
regrAvgX :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
regrAvgX = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_avgx"
regrAvgY :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
regrAvgY = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_avgy"
regrCount :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGint8)
regrCount = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGint8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_count"
regrIntercept :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
regrIntercept = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_intercept"
regrR2 :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
regrR2 = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_r2"
regrSlope :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
regrSlope = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_slope"
regrSxx :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
regrSxx = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_sxx"
regrSxy :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
regrSxy = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_sxy"
regrSyy :: AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
regrSyy = ByteString
-> AggregateArg
'[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null 'PGfloat8)
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"regr_syy"
stddev :: AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
stddev = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"stddev"
stddevPop :: AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
stddevPop = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"stddev_pop"
stddevSamp :: AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
stddevSamp = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"stddev_samp"
variance :: AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
variance = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"variance"
varPop :: AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
varPop = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"var_pop"
varSamp :: AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
varSamp = ByteString
-> AggregateArg '[null ty] lat with db params from
-> Expression
('Grouped bys) lat with db params from ('Null (PGAvg ty))
forall (xs :: [NullType]) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(bys :: [(Symbol, Symbol)]) (y :: NullType).
SListI xs =>
ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
"var_samp"
instance ( 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'.")
, a ~ AggregateArg
) => Aggregate a (Expression 'Ungrouped) where
countStar :: Expression 'Ungrouped lat with db params from ('NotNull 'PGint8)
countStar = Expression 'Ungrouped lat with db params from ('NotNull 'PGint8)
forall a. a
impossibleAggregateError
count :: a '[ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('NotNull 'PGint8)
count = a '[ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('NotNull 'PGint8)
forall a. a
impossibleAggregateError
sum_ :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGSum ty))
sum_ = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGSum ty))
forall a. a
impossibleAggregateError
arrayAgg :: a '[ty] lat with db params from
-> Expression
'Ungrouped lat with db params from ('Null ('PGvararray ty))
arrayAgg = a '[ty] lat with db params from
-> Expression
'Ungrouped lat with db params from ('Null ('PGvararray ty))
forall a. a
impossibleAggregateError
jsonAgg :: a '[ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGjson)
jsonAgg = a '[ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGjson)
forall a. a
impossibleAggregateError
jsonbAgg :: a '[ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGjsonb)
jsonbAgg = a '[ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGjsonb)
forall a. a
impossibleAggregateError
bitAnd :: a '[null int] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null int)
bitAnd = a '[null int] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null int)
forall a. a
impossibleAggregateError
bitOr :: a '[null int] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null int)
bitOr = a '[null int] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null int)
forall a. a
impossibleAggregateError
boolAnd :: a '[null 'PGbool] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGbool)
boolAnd = a '[null 'PGbool] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGbool)
forall a. a
impossibleAggregateError
boolOr :: a '[null 'PGbool] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGbool)
boolOr = a '[null 'PGbool] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGbool)
forall a. a
impossibleAggregateError
every :: a '[null 'PGbool] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGbool)
every = a '[null 'PGbool] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGbool)
forall a. a
impossibleAggregateError
max_ :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null ty)
max_ = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null ty)
forall a. a
impossibleAggregateError
min_ :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null ty)
min_ = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null ty)
forall a. a
impossibleAggregateError
avg :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
avg = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
forall a. a
impossibleAggregateError
corr :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
corr = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
covarPop :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
covarPop = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
covarSamp :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
covarSamp = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
regrAvgX :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
regrAvgX = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
regrAvgY :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
regrAvgY = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
regrCount :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGint8)
regrCount = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGint8)
forall a. a
impossibleAggregateError
regrIntercept :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
regrIntercept = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
regrR2 :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
regrR2 = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
regrSlope :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
regrSlope = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
regrSxx :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
regrSxx = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
regrSxy :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
regrSxy = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
regrSyy :: a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
regrSyy = a '[null 'PGfloat8, null 'PGfloat8] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null 'PGfloat8)
forall a. a
impossibleAggregateError
stddev :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
stddev = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
forall a. a
impossibleAggregateError
stddevPop :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
stddevPop = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
forall a. a
impossibleAggregateError
stddevSamp :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
stddevSamp = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
forall a. a
impossibleAggregateError
variance :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
variance = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
forall a. a
impossibleAggregateError
varPop :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
varPop = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
forall a. a
impossibleAggregateError
varSamp :: a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
varSamp = a '[null ty] lat with db params from
-> Expression 'Ungrouped lat with db params from ('Null (PGAvg ty))
forall a. a
impossibleAggregateError
impossibleAggregateError :: a
impossibleAggregateError :: a
impossibleAggregateError = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"impossible; called aggregate function for Ungrouped even though the Aggregate instance has a type error constraint."
unsafeAggregate
:: SOP.SListI xs
=> ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate :: ByteString
-> AggregateArg xs lat with db params from
-> Expression ('Grouped bys) lat with db params from y
unsafeAggregate ByteString
fun AggregateArg xs lat with db params from
xs = ByteString -> Expression ('Grouped bys) lat with db params from y
forall (grp :: Grouping) (lat :: [(Symbol, [(Symbol, NullType)])])
(with :: [(Symbol, [(Symbol, NullType)])]) (db :: SchemasType)
(params :: [NullType]) (from :: [(Symbol, [(Symbol, NullType)])])
(ty :: NullType).
ByteString -> Expression grp lat with db params from ty
UnsafeExpression (ByteString -> Expression ('Grouped bys) lat with db params from y)
-> ByteString
-> Expression ('Grouped bys) lat with db params from y
forall a b. (a -> b) -> a -> b
$ ByteString
fun ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> AggregateArg xs lat with db params from -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL AggregateArg xs lat with db params from
xs
type family PGSum ty where
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 )
type family PGAvg ty where
PGAvg 'PGint2 = 'PGnumeric
PGAvg 'PGint4 = 'PGnumeric
PGAvg 'PGint8 = 'PGnumeric
PGAvg 'PGnumeric = 'PGnumeric
PGAvg 'PGfloat4 = 'PGfloat8
PGAvg 'PGfloat8 = 'PGfloat8
PGAvg 'PGinterval = 'PGinterval
PGAvg pg = TypeError
('Text "Squeal type error: No average for " ':<>: 'ShowType pg)