| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Opaleye.Internal.Window
Synopsis
- newtype WindowFunction a b = WindowFunction (PackMap WndwOp PrimExpr a b)
- newtype Windows a b = Windows (PackMap (WndwOp, Window a) PrimExpr a b)
- runWindows' :: Applicative f => Windows a b -> ((WndwOp, Window a) -> f PrimExpr) -> a -> f b
- extractWindowFields :: Tag -> a -> (WndwOp, Window a) -> PM (Bindings (WndwOp, Partition)) PrimExpr
- noWindowFunction :: (a -> b) -> WindowFunction a b
- runWindows :: Windows a b -> Select a -> Select b
- windowsApply :: Windows (Windows a b, a) b
- makeWndw :: WindowFunction WndwOp (Field_ n a)
- makeWndwField :: (PrimExpr -> WndwOp) -> WindowFunction (Field_ n a) (Field_ n' a')
- makeWndwAny :: WndwOp -> WindowFunction a (Field_ n b)
- aggregatorWindowFunction :: Aggregator a b -> (a' -> a) -> WindowFunction a' b
- over :: WindowFunction a b -> Window a -> Order a -> Windows a b
- data Window a = Window (a -> [PrimExpr]) (Order a)
- partitionBy :: (a -> Field_ n b) -> Window a
- orderPartitionBy :: Order a -> Window a
Documentation
newtype WindowFunction a b Source #
WindowFunction represents expressions that contain window
 functions.
 You can choose a WindowFunction from the options below, and
 combine and manipulate them using the Applicative and
 Profunctor operations.
Constructors
| WindowFunction (PackMap WndwOp PrimExpr a b) | 
Instances
You can create Windows using over, and combine and manipulate
 them using the Applicative and Profunctor
 operations.
Instances
| Profunctor Windows Source # | |
| Defined in Opaleye.Internal.Window Methods dimap :: (a -> b) -> (c -> d) -> Windows b c -> Windows a d # lmap :: (a -> b) -> Windows b c -> Windows a c # rmap :: (b -> c) -> Windows a b -> Windows a c # (#.) :: forall a b c q. Coercible c b => q b c -> Windows a b -> Windows a c # (.#) :: forall a b c q. Coercible b a => Windows b c -> q a b -> Windows a c # | |
| Applicative (Windows a) Source # | |
| Defined in Opaleye.Internal.Window | |
| Functor (Windows a) Source # | |
runWindows' :: Applicative f => Windows a b -> ((WndwOp, Window a) -> f PrimExpr) -> a -> f b Source #
extractWindowFields :: Tag -> a -> (WndwOp, Window a) -> PM (Bindings (WndwOp, Partition)) PrimExpr Source #
noWindowFunction :: (a -> b) -> WindowFunction a b Source #
A WindowFunction that doesn't actually contain any window
 function.
runWindows :: Windows a b -> Select a -> Select b Source #
runWindows runs a query composed of expressions containing
 window
 functions.
 runWindows is similar to aggregate, with the main
 difference being that in a window query, each input row corresponds
 to one output row, whereas aggregation queries fold the entire
 input query down into a single row per group. In Haskell
 terminology, aggregate is to foldl as runWindows is
 to scanl.
windowsApply :: Windows (Windows a b, a) b Source #
makeWndwField :: (PrimExpr -> WndwOp) -> WindowFunction (Field_ n a) (Field_ n' a') Source #
makeWndwAny :: WndwOp -> WindowFunction a (Field_ n b) Source #
aggregatorWindowFunction :: Aggregator a b -> (a' -> a) -> WindowFunction a' b Source #
aggregatorWindowFunction allows the use of Aggregators in
 WindowFunctions. In particular, aggregatorWindowFunction
 sumover).
over :: WindowFunction a b -> Window a -> Order a -> Windows a b Source #
over applies a WindowFunction on a particular Window.  For
 example,
over (aggregatorWindowFunctionsumsalary) (partitionBydepartment) (descsalary)
If you want to use a Window that consists of the entire SELECT
 then supply mempty for the Window aWindow then supply mempty for the Order
 a
In PostgreSQL, window functions must specify the "window" over
 which they operate. The syntax for this looks like: SUM(salary)
 OVER (PARTITION BY department). The Opaleye type Window
 represents the segment consisting of the PARTIION BY.
You can create a Window using partitionBy and combine two
 Windows in a single one which combines the partition of both by
 using <>.
partitionBy :: (a -> Field_ n b) -> Window a Source #
The window where each partition shares the same value for the
 given Field.
orderPartitionBy :: Order a -> Window a Source #
Controls the order in which rows are processed by window functions. This does not need to match the ordering of the overall query.