opaleye-0.9.6.1: An SQL-generating DSL targeting PostgreSQL
Safe HaskellSafe-Inferred
LanguageHaskell2010

Opaleye.Internal.Aggregate

Synopsis

Documentation

newtype Aggregator a b Source #

An Aggregator takes a collection of rows of type a, groups them, and transforms each group into a single row of type b. This corresponds to aggregators using GROUP BY in SQL.

You should combine basic Aggregators into Aggregators on compound types by using the operations in Data.Profunctor.Product.

An Aggregator corresponds closely to a Fold from the foldl package. Whereas an Aggregator a b takes each group of type a to a single row of type b, a Fold a b takes a list of a and returns a single value of type b.

Instances

Instances details
ProductProfunctor Aggregator Source # 
Instance details

Defined in Opaleye.Internal.Aggregate

Methods

purePP :: b -> Aggregator a b #

(****) :: Aggregator a (b -> c) -> Aggregator a b -> Aggregator a c #

empty :: Aggregator () () #

(***!) :: Aggregator a b -> Aggregator a' b' -> Aggregator (a, a') (b, b') #

SumProfunctor Aggregator Source # 
Instance details

Defined in Opaleye.Internal.Aggregate

Methods

(+++!) :: Aggregator a b -> Aggregator a' b' -> Aggregator (Either a a') (Either b b') #

Profunctor Aggregator Source # 
Instance details

Defined in Opaleye.Internal.Aggregate

Methods

dimap :: (a -> b) -> (c -> d) -> Aggregator b c -> Aggregator a d #

lmap :: (a -> b) -> Aggregator b c -> Aggregator a c #

rmap :: (b -> c) -> Aggregator a b -> Aggregator a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Aggregator a b -> Aggregator a c #

(.#) :: forall a b c q. Coercible b a => Aggregator b c -> q a b -> Aggregator a c #

Applicative (Aggregator a) Source # 
Instance details

Defined in Opaleye.Internal.Aggregate

Methods

pure :: a0 -> Aggregator a a0 #

(<*>) :: Aggregator a (a0 -> b) -> Aggregator a a0 -> Aggregator a b #

liftA2 :: (a0 -> b -> c) -> Aggregator a a0 -> Aggregator a b -> Aggregator a c #

(*>) :: Aggregator a a0 -> Aggregator a b -> Aggregator a b #

(<*) :: Aggregator a a0 -> Aggregator a b -> Aggregator a a0 #

Functor (Aggregator a) Source # 
Instance details

Defined in Opaleye.Internal.Aggregate

Methods

fmap :: (a0 -> b) -> Aggregator a a0 -> Aggregator a b #

(<$) :: a0 -> Aggregator a b -> Aggregator a a0 #

orderAggregate :: Order a -> Aggregator a b -> Aggregator a b Source #

Order the values within each aggregation in Aggregator using the given ordering. This is only relevant for aggregations that depend on the order they get their elements, like arrayAgg and stringAgg.

You can either apply it to an aggregation of multiple columns, in which case it will apply to all aggregation functions in there

Example:

x :: Aggregator (Column a, Column b) (Column (PGArray a), Column (PGArray b))
x = orderAggregate (asc snd) $ p2 (arrayAgg, arrayAgg)

This will generate:

SELECT array_agg(a ORDER BY b ASC), array_agg(b ORDER BY b ASC)
FROM (SELECT a, b FROM ...)

Or you can apply it to a single column, and then compose the aggregations afterwards.

Example:

x :: Aggregator (Column a, Column b) (Column (PGArray a), Column (PGArray a))
x = (,) <$> orderAggregate (asc snd) (lmap fst arrayAgg)
        <*> orderAggregate (desc snd) (lmap fst arrayAgg)

This will generate:

SELECT array_agg(a ORDER BY b ASC), array_agg(a ORDER BY b DESC)
FROM (SELECT a, b FROM ...)