opaleye-0.8.0.1: An SQL-generating DSL targeting PostgreSQL
Safe HaskellNone
LanguageHaskell2010

Opaleye.Aggregate

Description

Perform aggregation on Selects. To aggregate a Select you should construct an Aggregator encoding how you want the aggregation to proceed, then call aggregate on it. The Aggregator should be constructed from the basic Aggregators below by using the combining operations from Data.Profunctor.Product.

Synopsis

Aggregation

aggregate :: Aggregator a b -> Select a -> Select b Source #

Given a Select producing rows of type a and an Aggregator accepting rows of type a, apply the aggregator to the select.

If you simply want to count the number of rows in a query you might find the countRows function more convenient.

If you want to use aggregate with SelectArrs then you should compose it with laterally:

laterally . aggregate :: Aggregator a b -> SelectArr a b -> SelectArr a b

Please note that when aggregating an empty query with no GROUP BY clause, Opaleye's behaviour differs from Postgres's behaviour. Postgres returns a single row whereas Opaleye returns zero rows. Opaleye's behaviour is consistent with the meaning of aggregating over groups of rows and Postgres's behaviour is inconsistent. When a query has zero rows it has zero groups, and thus zero rows in the result of an aggregation.

aggregateOrdered :: Order a -> Aggregator a b -> Select a -> Select 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.

Note that this orders all aggregations with the same ordering. If you need different orderings for different aggregations, use orderAggregate.

distinctAggregator :: Aggregator a b -> Aggregator a b Source #

Aggregate only distinct values

data 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
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 #

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') #

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 #

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 #

Basic Aggregators

groupBy :: Aggregator (Column a) (Column a) Source #

Group the aggregation by equality on the input to groupBy.

sum :: Aggregator (Column a) (Column a) Source #

Sum all rows in a group.

WARNING! The type of this operation is wrong and will crash at runtime when the argument is SqlInt4 or SqlInt8. For those use sumInt4 or sumInt8 instead.

count :: Aggregator (Column a) (Column SqlInt8) Source #

Count the number of non-null rows in a group.

countStar :: Aggregator a (Column SqlInt8) Source #

Count the number of rows in a group. This Aggregator is named countStar after SQL's COUNT(*) aggregation function.

max :: SqlOrd a => Aggregator (Column a) (Column a) Source #

Maximum of a group

min :: SqlOrd a => Aggregator (Column a) (Column a) Source #

Maximum of a group

jsonAgg :: Aggregator (Column a) (Column SqlJson) Source #

Aggregates values, including nulls, as a JSON array

An example usage:

import qualified Opaleye as O

O.aggregate O.jsonAgg $ do
    (firstCol, secondCol) <- O.selectTable table6
    return
      . O.jsonBuildObject
      $ O.jsonBuildObjectField "summary" firstCol
        <> O.jsonBuildObjectField "details" secondCol

The above query, when executed, will return JSON of the following form from postgres:

"[{\"summary\" : \"xy\", \"details\" : \"a\"}, {\"summary\" : \"z\", \"details\" : \"a\"}, {\"summary\" : \"more text\", \"details\" : \"a\"}]"

Counting rows

countRows :: Select a -> Select (Column SqlInt8) Source #

Count the number of rows in a query. This is different from aggregate count because it always returns exactly one row, even when the input query is empty.