module Rel8.Expr.Window
( cumulative
, rowNumber
, rank
, denseRank
, percentRank
, cumeDist
, ntile
, lag
, lead
, firstValue
, lastValue
, nthValue
)
where
import Data.Int ( Int32, Int64 )
import Prelude
import qualified Opaleye.Internal.Aggregate as Opaleye
import qualified Opaleye.Internal.PackMap as Opaleye
import qualified Opaleye.Internal.Window as Opaleye
import qualified Opaleye.Window as Opaleye
import Data.Profunctor (dimap)
import Rel8.Aggregate ( Aggregate( Aggregate ) )
import Rel8.Expr ( Expr )
import Rel8.Expr.Opaleye ( fromColumn, fromPrimExpr, toColumn, toPrimExpr )
import Rel8.Schema.Null ( Nullify )
import Rel8.Window ( Window( Window ) )
cumulative :: (a -> Aggregate b) -> Window a (Expr b)
cumulative :: forall a b. (a -> Aggregate b) -> Window a (Expr b)
cumulative a -> Aggregate b
f =
forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$ forall a b a'. Aggregator a b -> (a' -> a) -> WindowFunction a' b
Opaleye.aggregatorWindowFunction (forall a b. (a -> Aggregate b) -> Aggregator a (Expr b)
fromAggregate a -> Aggregate b
f) forall a. a -> a
id
rowNumber :: Window a (Expr Int64)
rowNumber :: forall a. Window a (Expr Int64)
rowNumber = forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$ forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. WindowFunction a (Field_ 'NonNullable SqlInt8)
Opaleye.rowNumber
rank :: Window a (Expr Int64)
rank :: forall a. Window a (Expr Int64)
rank = forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$ forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. WindowFunction a (Field_ 'NonNullable SqlInt8)
Opaleye.rank
denseRank :: Window a (Expr Int64)
denseRank :: forall a. Window a (Expr Int64)
denseRank = forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$ forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. WindowFunction a (Field_ 'NonNullable SqlInt8)
Opaleye.denseRank
percentRank :: Window a (Expr Double)
percentRank :: forall a. Window a (Expr Double)
percentRank = forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$ forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. WindowFunction a (Field_ 'NonNullable SqlFloat8)
Opaleye.percentRank
cumeDist :: Window a (Expr Double)
cumeDist :: forall a. Window a (Expr Double)
cumeDist = forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$ forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. WindowFunction a (Field_ 'NonNullable SqlFloat8)
Opaleye.cumeDist
ntile :: Expr Int32 -> Window a (Expr Int32)
ntile :: forall a. Expr Int32 -> Window a (Expr Int32)
ntile Expr Int32
buckets = forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$ forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
forall a.
Field_ 'NonNullable SqlInt4
-> WindowFunction a (Field_ 'NonNullable SqlInt4)
Opaleye.ntile (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn (forall a. Expr a -> PrimExpr
toPrimExpr Expr Int32
buckets))
lag :: Expr Int32 -> Expr a -> Window (Expr a) (Expr a)
lag :: forall a. Expr Int32 -> Expr a -> Window (Expr a) (Expr a)
lag Expr Int32
offset Expr a
def =
forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Expr a -> PrimExpr
toPrimExpr) (forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn) forall a b. (a -> b) -> a -> b
$
forall (n :: Nullability) a.
Field_ 'NonNullable SqlInt4
-> Field_ n a -> WindowFunction (Field_ n a) (Field_ n a)
Opaleye.lag (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn (forall a. Expr a -> PrimExpr
toPrimExpr Expr Int32
offset)) (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn (forall a. Expr a -> PrimExpr
toPrimExpr Expr a
def))
lead :: Expr Int32 -> Expr a -> Window (Expr a) (Expr a)
lead :: forall a. Expr Int32 -> Expr a -> Window (Expr a) (Expr a)
lead Expr Int32
offset Expr a
def =
forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Expr a -> PrimExpr
toPrimExpr) (forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn) forall a b. (a -> b) -> a -> b
$
forall (n :: Nullability) a.
Field_ 'NonNullable SqlInt4
-> Field_ n a -> WindowFunction (Field_ n a) (Field_ n a)
Opaleye.lead (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn (forall a. Expr a -> PrimExpr
toPrimExpr Expr Int32
offset)) (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn (forall a. Expr a -> PrimExpr
toPrimExpr Expr a
def))
firstValue :: Window (Expr a) (Expr a)
firstValue :: forall a. Window (Expr a) (Expr a)
firstValue =
forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Expr a -> PrimExpr
toPrimExpr) (forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn)
forall (n :: Nullability) a.
WindowFunction (Field_ n a) (Field_ n a)
Opaleye.firstValue
lastValue :: Window (Expr a) (Expr a)
lastValue :: forall a. Window (Expr a) (Expr a)
lastValue =
forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Expr a -> PrimExpr
toPrimExpr) (forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn)
forall (n :: Nullability) a.
WindowFunction (Field_ n a) (Field_ n a)
Opaleye.lastValue
nthValue :: Expr Int32 -> Window (Expr a) (Expr (Nullify a))
nthValue :: forall a. Expr Int32 -> Window (Expr a) (Expr (Nullify a))
nthValue Expr Int32
n =
forall a b. WindowFunction a b -> Window a b
fromWindowFunction forall a b. (a -> b) -> a -> b
$
forall (p :: * -> * -> *) a b c d.
Profunctor p =>
(a -> b) -> (c -> d) -> p b c -> p a d
dimap (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Expr a -> PrimExpr
toPrimExpr) (forall a. PrimExpr -> Expr a
fromPrimExpr forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (n :: Nullability) b. Field_ n b -> PrimExpr
fromColumn) forall a b. (a -> b) -> a -> b
$
forall (n :: Nullability) a.
Field_ 'NonNullable SqlInt4
-> WindowFunction (Field_ n a) (FieldNullable a)
Opaleye.nthValue (forall (n :: Nullability) b. PrimExpr -> Field_ n b
toColumn (forall a. Expr a -> PrimExpr
toPrimExpr Expr Int32
n))
fromAggregate :: (a -> Aggregate b) -> Opaleye.Aggregator a (Expr b)
fromAggregate :: forall a b. (a -> Aggregate b) -> Aggregator a (Expr b)
fromAggregate a -> Aggregate b
f = forall a b.
PackMap
(Maybe (AggrOp, [OrderExpr], AggrDistinct), PrimExpr) PrimExpr a b
-> Aggregator a b
Opaleye.Aggregator forall a b. (a -> b) -> a -> b
$ forall a b s t.
(forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t)
-> PackMap a b s t
Opaleye.PackMap forall a b. (a -> b) -> a -> b
$ \(Maybe (AggrOp, [OrderExpr], AggrDistinct), PrimExpr) -> f PrimExpr
w a
a -> case a -> Aggregate b
f a
a of
Aggregate (Opaleye.Aggregator (Opaleye.PackMap forall (f :: * -> *).
Applicative f =>
((Maybe (AggrOp, [OrderExpr], AggrDistinct), PrimExpr)
-> f PrimExpr)
-> () -> f (Expr b)
x)) -> forall (f :: * -> *).
Applicative f =>
((Maybe (AggrOp, [OrderExpr], AggrDistinct), PrimExpr)
-> f PrimExpr)
-> () -> f (Expr b)
x (Maybe (AggrOp, [OrderExpr], AggrDistinct), PrimExpr) -> f PrimExpr
w ()
fromWindowFunction :: Opaleye.WindowFunction a b -> Window a b
fromWindowFunction :: forall a b. WindowFunction a b -> Window a b
fromWindowFunction (Opaleye.WindowFunction (Opaleye.PackMap forall (f :: * -> *).
Applicative f =>
(WndwOp -> f PrimExpr) -> a -> f b
w)) =
forall a b. Windows a b -> Window a b
Window forall a b. (a -> b) -> a -> b
$ forall a b. PackMap (WndwOp, Window a) PrimExpr a b -> Windows a b
Opaleye.Windows forall a b. (a -> b) -> a -> b
$ forall a b s t.
(forall (f :: * -> *). Applicative f => (a -> f b) -> s -> f t)
-> PackMap a b s t
Opaleye.PackMap forall a b. (a -> b) -> a -> b
$ \(WndwOp, Window a) -> f PrimExpr
f -> forall (f :: * -> *).
Applicative f =>
(WndwOp -> f PrimExpr) -> a -> f b
w forall a b. (a -> b) -> a -> b
$ \WndwOp
o -> (WndwOp, Window a) -> f PrimExpr
f (WndwOp
o, forall a. Monoid a => a
mempty)