module Database.Beam.Query.Aggregate
(
aggregate_
, filterWhere_, filterWhere_'
, QGroupable(..)
, sum_, avg_, min_, max_, count_, countAll_
, rank_, cumeDist_, percentRank_, denseRank_
, rowNumber_
, every_, any_, some_
, sumOver_, avgOver_, minOver_, maxOver_, countOver_
, everyOver_, anyOver_, someOver_
, distinctInGroup_, allInGroup_, allInGroupExplicitly_
) where
import Database.Beam.Query.Internal
import Database.Beam.Query.Operator
import Database.Beam.Query.Ord
import Database.Beam.Backend.SQL
import Database.Beam.Schema.Tables
import Control.Applicative
import Control.Monad.Writer
import Control.Monad.Free
import Data.Typeable
type Aggregable be a =
ProjectibleWithPredicate AggregateContext be (WithExprContext (BeamSqlBackendExpressionSyntax' be)) a
aggregate_ :: forall be a r db s.
( BeamSqlBackend be
, Aggregable be a, Projectible be r, Projectible be a
, ContextRewritable a
, ThreadRewritable (QNested s) (WithRewrittenContext a QValueContext)
)
=> (r -> a)
-> Q be db (QNested s) r
-> Q be db s (WithRewrittenThread (QNested s) s (WithRewrittenContext a QValueContext))
aggregate_ mkAggregation (Q aggregating) =
Q (liftF (QAggregate mkAggregation' aggregating (rewriteThread (Proxy @s) . rewriteContext (Proxy @QValueContext))))
where
mkAggregation' x tblPfx =
let agg = mkAggregation x
doProject :: AggregateContext c
=> Proxy c -> Proxy be
-> WithExprContext (BeamSqlBackendExpressionSyntax' be)
-> Writer [WithExprContext (BeamSqlBackendExpressionSyntax' be)]
(WithExprContext (BeamSqlBackendExpressionSyntax' be))
doProject p _ expr =
case cast p of
Just (Proxy :: Proxy QGroupingContext) ->
tell [ expr ] >> pure expr
Nothing ->
case cast p of
Just (Proxy :: Proxy QAggregateContext) ->
pure expr
Nothing -> error "aggregate_: impossible"
groupingExprs =
fmap (fmap fromBeamSqlBackendExpressionSyntax) $
execWriter (project' (Proxy @AggregateContext) (Proxy @(be, WithExprContext (BeamSqlBackendExpressionSyntax' be))) doProject agg)
in case groupingExprs of
[] -> (Nothing, agg)
_ -> (Just (groupByExpressions (sequenceA groupingExprs tblPfx)), agg)
class QGroupable expr grouped | expr -> grouped, grouped -> expr where
group_ :: expr -> grouped
instance QGroupable (QExpr be s a) (QGroupExpr be s a) where
group_ (QExpr a) = QExpr a
instance Beamable tbl =>
QGroupable (tbl (QExpr be s)) (tbl (QGroupExpr be s)) where
group_ = changeBeamRep (\(Columnar' (QExpr x)) -> Columnar' (QExpr x))
instance Beamable tbl =>
QGroupable (tbl (Nullable (QExpr be s))) (tbl (Nullable (QGroupExpr be s))) where
group_ = changeBeamRep (\(Columnar' (QExpr x)) -> Columnar' (QExpr x))
allInGroup_ :: IsSql92AggregationSetQuantifierSyntax s
=> Maybe s
allInGroup_ = Nothing
distinctInGroup_ :: IsSql92AggregationSetQuantifierSyntax s
=> Maybe s
distinctInGroup_ = Just setQuantifierDistinct
allInGroupExplicitly_ :: IsSql92AggregationSetQuantifierSyntax s
=> Maybe s
allInGroupExplicitly_ = Just setQuantifierAll
min_ :: BeamSqlBackend be
=> QExpr be s a -> QAgg be s (Maybe a)
min_ = minOver_ allInGroup_
max_ :: BeamSqlBackend be
=> QExpr be s a -> QAgg be s (Maybe a)
max_ = maxOver_ allInGroup_
avg_ :: ( BeamSqlBackend be, Num a )
=> QExpr be s a -> QAgg be s (Maybe a)
avg_ = avgOver_ allInGroup_
sum_ :: ( BeamSqlBackend be, Num a )
=> QExpr be s a -> QAgg be s (Maybe a)
sum_ = sumOver_ allInGroup_
countAll_ :: BeamSqlBackend be => QAgg be s Int
countAll_ = QExpr (pure countAllE)
count_ :: ( BeamSqlBackend be, Integral b )
=> QExpr be s a -> QAgg be s b
count_ (QExpr over) = QExpr (countE Nothing <$> over)
cumeDist_ :: BeamSqlT612Backend be
=> QAgg be s Double
cumeDist_ = QExpr (pure cumeDistAggE)
percentRank_ :: BeamSqlT612Backend be
=> QAgg be s Double
percentRank_ = QExpr (pure percentRankAggE)
denseRank_ :: BeamSqlT612Backend be
=> QAgg be s Int
denseRank_ = QExpr (pure denseRankAggE)
rowNumber_ :: BeamSql2003ExpressionBackend be
=> QAgg be s Int
rowNumber_ = QExpr (pure rowNumberE)
rank_ :: BeamSqlT611Backend be
=> QAgg be s Int
rank_ = QExpr (pure rankAggE)
minOver_, maxOver_
:: BeamSqlBackend be
=> Maybe (BeamSqlBackendAggregationQuantifierSyntax be)
-> QExpr be s a -> QAgg be s (Maybe a)
minOver_ q (QExpr a) = QExpr (minE q <$> a)
maxOver_ q (QExpr a) = QExpr (maxE q <$> a)
avgOver_, sumOver_
:: ( BeamSqlBackend be, Num a )
=> Maybe (BeamSqlBackendAggregationQuantifierSyntax be)
-> QExpr be s a -> QAgg be s (Maybe a)
avgOver_ q (QExpr a) = QExpr (avgE q <$> a)
sumOver_ q (QExpr a) = QExpr (sumE q <$> a)
countOver_
:: ( BeamSqlBackend be, Integral b )
=> Maybe (BeamSqlBackendAggregationQuantifierSyntax be)
-> QExpr be s a -> QAgg be s b
countOver_ q (QExpr a) = QExpr (countE q <$> a)
everyOver_, someOver_, anyOver_
:: BeamSql99AggregationBackend be
=> Maybe (BeamSqlBackendAggregationQuantifierSyntax be)
-> QExpr be s SqlBool -> QAgg be s SqlBool
everyOver_ q (QExpr a) = QExpr (everyE q <$> a)
someOver_ q (QExpr a) = QExpr (someE q <$> a)
anyOver_ q (QExpr a) = QExpr (anyE q <$> a)
filterWhere_ :: BeamSqlT611Backend be
=> QAgg be s a -> QExpr be s Bool -> QAgg be s a
filterWhere_ agg cond = filterWhere_' agg (sqlBool_ cond)
filterWhere_' :: BeamSqlT611Backend be
=> QAgg be s a -> QExpr be s SqlBool -> QAgg be s a
filterWhere_' (QExpr agg) (QExpr cond) = QExpr (liftA2 filterAggE agg cond)
every_ :: BeamSql99AggregationBackend be
=> QExpr be s SqlBool -> QAgg be s SqlBool
every_ = everyOver_ allInGroup_
some_ :: BeamSql99AggregationBackend be
=> QExpr be s SqlBool -> QAgg be s SqlBool
some_ = someOver_ allInGroup_
any_ :: BeamSql99AggregationBackend be
=> QExpr be s SqlBool -> QAgg be s SqlBool
any_ = anyOver_ allInGroup_