Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Window functions and definitions
Synopsis
- partitionBy :: SListI bys => NP (Expression outer commons grp schemas params from) bys -> WindowDefinition outer commons grp schemas params from
- rank :: WinFun0 (NotNull PGint8)
- rowNumber :: WinFun0 (NotNull PGint8)
- denseRank :: WinFun0 (NotNull PGint8)
- percentRank :: WinFun0 (NotNull PGfloat8)
- cumeDist :: WinFun0 (NotNull PGfloat8)
- ntile :: WinFun1 (NotNull PGint4) (NotNull PGint4)
- lag :: WinFunN '[ty, NotNull PGint4, ty] ty
- lead :: WinFunN '[ty, NotNull PGint4, ty] ty
- firstValue :: WinFun1 ty ty
- lastValue :: WinFun1 ty ty
- nthValue :: WinFunN '[null ty, NotNull PGint4] (Null ty)
- unsafeWindowFunction1 :: ByteString -> WinFun1 x y
- unsafeWindowFunctionN :: SListI xs => ByteString -> WinFunN xs y
- newtype WindowFunction (outer :: FromType) (commons :: FromType) (grp :: Grouping) (schemas :: SchemasType) (params :: [NullityType]) (from :: FromType) (ty :: NullityType) = UnsafeWindowFunction {}
- data WindowDefinition outer commons grp schemas params from where
- WindowDefinition :: SListI bys => NP (Expression outer commons grp schemas params from) bys -> [SortExpression outer commons grp schemas params from] -> WindowDefinition outer commons grp schemas params from
- type WinFun0 x = forall outer commons grp schemas params from. WindowFunction outer commons grp schemas params from x
- type WinFun1 x y = forall outer commons grp schemas params from. Expression outer commons grp schemas params from x -> WindowFunction outer commons grp schemas params from y
- type WinFunN xs y = forall outer commons grp schemas params from. NP (Expression outer commons grp schemas params from) xs -> WindowFunction outer commons grp schemas params from y
functions
:: SListI bys | |
=> NP (Expression outer commons grp schemas params from) bys | partitions |
-> WindowDefinition outer commons grp schemas params from |
The partitionBy
clause within Over
divides the rows into groups,
or partitions, that share the same values of the partitionBy
Expression
(s).
For each row, the window function is computed across the rows that fall into
the same partition as the current row.
rank :: WinFun0 (NotNull PGint8) Source #
rank of the current row with gaps; same as rowNumber
of its first peer
>>>
printSQL rank
rank()
rowNumber :: WinFun0 (NotNull PGint8) Source #
number of the current row within its partition, counting from 1
>>>
printSQL rowNumber
row_number()
denseRank :: WinFun0 (NotNull PGint8) Source #
rank of the current row without gaps; this function counts peer groups
>>>
printSQL denseRank
dense_rank()
percentRank :: WinFun0 (NotNull PGfloat8) Source #
relative rank of the current row: (rank - 1) / (total partition rows - 1)
>>>
printSQL percentRank
percent_rank()
cumeDist :: WinFun0 (NotNull PGfloat8) Source #
cumulative distribution: (number of partition rows preceding or peer with current row) / total partition rows
>>>
printSQL cumeDist
cume_dist()
ntile :: WinFun1 (NotNull PGint4) (NotNull PGint4) Source #
integer ranging from 1 to the argument value, dividing the partition as equally as possible
>>>
printSQL $ ntile 5
ntile(5)
lag :: WinFunN '[ty, NotNull PGint4, ty] ty Source #
returns value evaluated at the row that is offset rows before the current row within the partition; if there is no such row, instead return default (which must be of the same type as value). Both offset and default are evaluated with respect to the current row.
lead :: WinFunN '[ty, NotNull PGint4, ty] ty Source #
returns value evaluated at the row that is offset rows after the current row within the partition; if there is no such row, instead return default (which must be of the same type as value). Both offset and default are evaluated with respect to the current row.
firstValue :: WinFun1 ty ty Source #
returns value evaluated at the row that is the first row of the window frame
lastValue :: WinFun1 ty ty Source #
returns value evaluated at the row that is the last row of the window frame
nthValue :: WinFunN '[null ty, NotNull PGint4] (Null ty) Source #
returns value evaluated at the row that is the nth row of the window frame (counting from 1); null if no such row
unsafeWindowFunction1 :: ByteString -> WinFun1 x y Source #
escape hatch for defining window functions
unsafeWindowFunctionN :: SListI xs => ByteString -> WinFunN xs y Source #
escape hatch for defining multi-argument window functions
types
newtype WindowFunction (outer :: FromType) (commons :: FromType) (grp :: Grouping) (schemas :: SchemasType) (params :: [NullityType]) (from :: FromType) (ty :: NullityType) Source #
A window function performs a calculation across a set of table rows that are somehow related to the current row. This is comparable to the type of calculation that can be done with an aggregate function. However, window functions do not cause rows to become grouped into a single output row like non-window aggregate calls would. Instead, the rows retain their separate identities. Behind the scenes, the window function is able to access more than just the current row of the query result.
Instances
Aggregate (Expression outer commons grp schemas params from) (NP (Expression outer commons grp schemas params from) :: [NullityType] -> Type) (WindowFunction outer commons grp schemas params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window countStar :: WindowFunction outer commons grp schemas params from (NotNull PGint8) Source # count :: Expression outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from (NotNull PGint8) Source # sum_ :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGSum ty)) Source # arrayAgg :: Expression outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from (Null (PGvararray ty)) Source # jsonAgg :: Expression outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from (Null PGjson) Source # jsonbAgg :: Expression outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from (Null PGjsonb) Source # bitAnd :: In int PGIntegral => Expression outer commons grp schemas params from (null int) -> WindowFunction outer commons grp schemas params from (Null int) Source # bitOr :: In int PGIntegral => Expression outer commons grp schemas params from (null int) -> WindowFunction outer commons grp schemas params from (Null int) Source # boolAnd :: Expression outer commons grp schemas params from (null PGbool) -> WindowFunction outer commons grp schemas params from (Null PGbool) Source # boolOr :: Expression outer commons grp schemas params from (null PGbool) -> WindowFunction outer commons grp schemas params from (Null PGbool) Source # every :: Expression outer commons grp schemas params from (null PGbool) -> WindowFunction outer commons grp schemas params from (Null PGbool) Source # max_ :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null ty) Source # min_ :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null ty) Source # avg :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source # corr :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # covarPop :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # covarSamp :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # regrAvgX :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # regrAvgY :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # regrCount :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGint8) Source # regrIntercept :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # regrR2 :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # regrSlope :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # regrSxx :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # regrSxy :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # regrSyy :: NP (Expression outer commons grp schemas params from) (null PGfloat8 ': (null PGfloat8 ': [])) -> WindowFunction outer commons grp schemas params from (Null PGfloat8) Source # stddev :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source # stddevPop :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source # stddevSamp :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source # variance :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source # varPop :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source # varSamp :: Expression outer commons grp schemas params from (null ty) -> WindowFunction outer commons grp schemas params from (Null (PGAvg ty)) Source # | |
Eq (WindowFunction outer commons grp schemas params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window (==) :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> Bool # (/=) :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> Bool # | |
Ord (WindowFunction outer commons grp schemas params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window compare :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> Ordering # (<) :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> Bool # (<=) :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> Bool # (>) :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> Bool # (>=) :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> Bool # max :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty # min :: WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty -> WindowFunction outer commons grp schemas params from ty # | |
Show (WindowFunction outer commons grp schemas params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window showsPrec :: Int -> WindowFunction outer commons grp schemas params from ty -> ShowS # show :: WindowFunction outer commons grp schemas params from ty -> String # showList :: [WindowFunction outer commons grp schemas params from ty] -> ShowS # | |
Generic (WindowFunction outer commons grp schemas params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window type Rep (WindowFunction outer commons grp schemas params from ty) :: Type -> Type # from :: WindowFunction outer commons grp schemas params from ty -> Rep (WindowFunction outer commons grp schemas params from ty) x # to :: Rep (WindowFunction outer commons grp schemas params from ty) x -> WindowFunction outer commons grp schemas params from ty # | |
NFData (WindowFunction outer commons grp schemas params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window rnf :: WindowFunction outer commons grp schemas params from ty -> () # | |
RenderSQL (WindowFunction outer commons grp schemas params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window renderSQL :: WindowFunction outer commons grp schemas params from ty -> ByteString Source # | |
type Rep (WindowFunction outer commons grp schemas params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window type Rep (WindowFunction outer commons grp schemas params from ty) = D1 (MetaData "WindowFunction" "Squeal.PostgreSQL.Expression.Window" "squeal-postgresql-0.5.2.0-4fAomBtpMjd6mRwLthA4w2" True) (C1 (MetaCons "UnsafeWindowFunction" PrefixI True) (S1 (MetaSel (Just "renderWindowFunction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
data WindowDefinition outer commons grp schemas params from where Source #
A WindowDefinition
is a set of table rows that are somehow related
to the current row
WindowDefinition | |
|
Instances
OrderBy WindowDefinition Source # | |
Defined in Squeal.PostgreSQL.Expression.Window orderBy :: [SortExpression outer commons grp schemas params from] -> WindowDefinition outer commons grp schemas params from -> WindowDefinition outer commons grp schemas params from Source # | |
RenderSQL (WindowDefinition outer commons schemas from grp params) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window renderSQL :: WindowDefinition outer commons schemas from grp params -> ByteString Source # |
= WindowFunction outer commons grp schemas params from x | cannot reference aliases |
A RankNType
for window functions with no arguments.
= Expression outer commons grp schemas params from x | input |
-> WindowFunction outer commons grp schemas params from y | output |
A RankNType
for window functions with 1 argument.
= NP (Expression outer commons grp schemas params from) xs | inputs |
-> WindowFunction outer commons grp schemas params from y | output |
A RankNType
for window functions with a fixed-length
list of heterogeneous arguments.
Use the *:
operator to end your argument lists.