| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
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
- aggregate :: Default Unpackspec a a => Aggregator a b -> Select a -> Select b
- aggregateOrdered :: Default Unpackspec a a => Order a -> Aggregator a b -> Select a -> Select b
- distinctAggregator :: Aggregator a b -> Aggregator a b
- filterWhere :: (a -> Field SqlBool) -> Aggregator a b -> Aggregator a (MaybeFields b)
- data Aggregator a b
- groupBy :: Aggregator (Field_ n a) (Field_ n a)
- sum :: Aggregator (Field a) (Field a)
- sumInt4 :: Aggregator (Field SqlInt4) (Field SqlInt8)
- sumInt8 :: Aggregator (Field SqlInt8) (Field SqlNumeric)
- count :: Aggregator (Field a) (Field SqlInt8)
- countStar :: Aggregator a (Field SqlInt8)
- avg :: Aggregator (Field SqlFloat8) (Field SqlFloat8)
- max :: SqlOrd a => Aggregator (Field a) (Field a)
- min :: SqlOrd a => Aggregator (Field a) (Field a)
- boolOr :: Aggregator (Field SqlBool) (Field SqlBool)
- boolAnd :: Aggregator (Field SqlBool) (Field SqlBool)
- arrayAgg :: Aggregator (Field a) (Field (SqlArray a))
- arrayAgg_ :: Aggregator (Field_ n a) (Field (SqlArray_ n a))
- jsonAgg :: Aggregator (Field a) (Field SqlJson)
- stringAgg :: Field SqlText -> Aggregator (Field SqlText) (Field SqlText)
- countRows :: Select a -> Select (Field SqlInt8)
- aggregateExplicit :: Unpackspec a a' -> Aggregator a' b -> Select a -> Select b
Aggregation
aggregate :: Default Unpackspec a a => 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::Aggregatora b ->SelectArra b ->SelectArra 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 :: Default Unpackspec a a => Order a -> Aggregator a b -> Select a -> Select b Source #
distinctAggregator :: Aggregator a b -> Aggregator a b Source #
Aggregate only distinct values
filterWhere :: (a -> Field SqlBool) -> Aggregator a b -> Aggregator a (MaybeFields b) Source #
Aggregate only rows matching the given predicate
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
Basic Aggregators
groupBy :: Aggregator (Field_ n a) (Field_ n a) Source #
Group the aggregation by equality on the input to groupBy.
sumInt8 :: Aggregator (Field SqlInt8) (Field SqlNumeric) Source #
countStar :: Aggregator a (Field SqlInt8) Source #
Count the number of rows in a group. This Aggregator is named
countStar after SQL's COUNT(*) aggregation function.
jsonAgg :: Aggregator (Field a) (Field SqlJson) Source #
Aggregates values 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
Explicit
aggregateExplicit :: Unpackspec a 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.