Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | [email protected] |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Squeal.PostgreSQL.Expression.Window
Description
window functions, arguments and definitions
Synopsis
- data WindowDefinition grp lat with db params from where
- WindowDefinition :: SListI bys => NP (Expression grp lat with db params from) bys -> [SortExpression grp lat with db params from] -> WindowDefinition grp lat with db params from
- partitionBy :: SListI bys => NP (Expression grp lat with db params from) bys -> WindowDefinition grp lat with db params from
- newtype WindowFunction (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (ty :: NullType) = UnsafeWindowFunction {}
- data WindowArg (grp :: Grouping) (args :: [NullType]) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) = WindowArg {
- windowArgs :: NP (Expression grp lat with db params from) args
- windowFilter :: [Condition grp lat with db params from]
- pattern Window :: Expression grp lat with db params from arg -> WindowArg grp '[arg] lat with db params from
- pattern Windows :: NP (Expression grp lat with db params from) args -> WindowArg grp args lat with db params from
- type WinFun0 x = forall grp lat with db params from. WindowFunction grp lat with db params from x
- type (-#->) x y = forall grp lat with db params from. WindowArg grp '[x] lat with db params from -> WindowFunction grp lat with db params from y
- type (--#->) xs y = forall grp lat with db params from. WindowArg grp xs lat with db params from -> WindowFunction grp lat with db params from y
- rank :: WinFun0 (NotNull PGint8)
- rowNumber :: WinFun0 (NotNull PGint8)
- denseRank :: WinFun0 (NotNull PGint8)
- percentRank :: WinFun0 (NotNull PGfloat8)
- cumeDist :: WinFun0 (NotNull PGfloat8)
- ntile :: NotNull PGint4 -#-> NotNull PGint4
- lag :: '[ty, NotNull PGint4, ty] --#-> ty
- lead :: '[ty, NotNull PGint4, ty] --#-> ty
- firstValue :: ty -#-> ty
- lastValue :: ty -#-> ty
- nthValue :: '[null ty, NotNull PGint4] --#-> Null ty
- unsafeWindowFunction1 :: ByteString -> x -#-> y
- unsafeWindowFunctionN :: SListI xs => ByteString -> xs --#-> y
Window Definition
data WindowDefinition grp lat with db params from where Source #
A WindowDefinition
is a set of table rows that are somehow related
to the current row
Constructors
WindowDefinition | |
Fields
|
Instances
OrderBy (WindowDefinition grp) grp Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods orderBy :: [SortExpression grp lat with db params from] -> WindowDefinition grp lat with db params from -> WindowDefinition grp lat with db params from Source # | |
RenderSQL (WindowDefinition lat with db from grp params) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods renderSQL :: WindowDefinition lat with db from grp params -> ByteString Source # |
Arguments
:: SListI bys | |
=> NP (Expression grp lat with db params from) bys | partitions |
-> WindowDefinition grp lat with db 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.
Window Function
Types
newtype WindowFunction (grp :: Grouping) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (ty :: NullType) 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.
Constructors
UnsafeWindowFunction | |
Fields |
Instances
Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods countStar :: WindowFunction grp lat with db params from (NotNull PGint8) Source # count :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (NotNull PGint8) Source # sum_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGSum ty)) Source # arrayAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGvararray ty)) Source # jsonAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGjson) Source # jsonbAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGjsonb) Source # bitAnd :: In int PGIntegral => WindowArg grp (null int ': []) lat with db params from -> WindowFunction grp lat with db params from (Null int) Source # bitOr :: In int PGIntegral => WindowArg grp (null int ': []) lat with db params from -> WindowFunction grp lat with db params from (Null int) Source # boolAnd :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # boolOr :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # every :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # max_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null ty) Source # min_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null ty) Source # avg :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # corr :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # covarPop :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # covarSamp :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrAvgX :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrAvgY :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrCount :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGint8) Source # regrIntercept :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrR2 :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSlope :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSxx :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSxy :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSyy :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # stddev :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # stddevPop :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # stddevSamp :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # variance :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # varPop :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # varSamp :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # | |
Eq (WindowFunction grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods (==) :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> Bool # (/=) :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> Bool # | |
Ord (WindowFunction grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods compare :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> Ordering # (<) :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> Bool # (<=) :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> Bool # (>) :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> Bool # (>=) :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> Bool # max :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty # min :: WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty -> WindowFunction grp lat with db params from ty # | |
Show (WindowFunction grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods showsPrec :: Int -> WindowFunction grp lat with db params from ty -> ShowS # show :: WindowFunction grp lat with db params from ty -> String # showList :: [WindowFunction grp lat with db params from ty] -> ShowS # | |
Generic (WindowFunction grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Associated Types type Rep (WindowFunction grp lat with db params from ty) :: Type -> Type # Methods from :: WindowFunction grp lat with db params from ty -> Rep (WindowFunction grp lat with db params from ty) x # to :: Rep (WindowFunction grp lat with db params from ty) x -> WindowFunction grp lat with db params from ty # | |
NFData (WindowFunction grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods rnf :: WindowFunction grp lat with db params from ty -> () # | |
RenderSQL (WindowFunction grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods renderSQL :: WindowFunction grp lat with db params from ty -> ByteString Source # | |
type Rep (WindowFunction grp lat with db params from ty) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window type Rep (WindowFunction grp lat with db params from ty) = D1 (MetaData "WindowFunction" "Squeal.PostgreSQL.Expression.Window" "squeal-postgresql-0.6.0.1-2mcKKIXTe9UEFlpcl38Onr" True) (C1 (MetaCons "UnsafeWindowFunction" PrefixI True) (S1 (MetaSel (Just "renderWindowFunction") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))) |
data WindowArg (grp :: Grouping) (args :: [NullType]) (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) Source #
WindowArg
s are used for the input of WindowFunction
s.
Constructors
WindowArg | |
Fields
|
Instances
Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods countStar :: WindowFunction grp lat with db params from (NotNull PGint8) Source # count :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (NotNull PGint8) Source # sum_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGSum ty)) Source # arrayAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGvararray ty)) Source # jsonAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGjson) Source # jsonbAgg :: WindowArg grp (ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGjsonb) Source # bitAnd :: In int PGIntegral => WindowArg grp (null int ': []) lat with db params from -> WindowFunction grp lat with db params from (Null int) Source # bitOr :: In int PGIntegral => WindowArg grp (null int ': []) lat with db params from -> WindowFunction grp lat with db params from (Null int) Source # boolAnd :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # boolOr :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # every :: WindowArg grp (null PGbool ': []) lat with db params from -> WindowFunction grp lat with db params from (Null PGbool) Source # max_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null ty) Source # min_ :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null ty) Source # avg :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # corr :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # covarPop :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # covarSamp :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrAvgX :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrAvgY :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrCount :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGint8) Source # regrIntercept :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrR2 :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSlope :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSxx :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSxy :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # regrSyy :: WindowArg grp (null PGfloat8 ': (null PGfloat8 ': [])) lat with db params from -> WindowFunction grp lat with db params from (Null PGfloat8) Source # stddev :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # stddevPop :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # stddevSamp :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # variance :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # varPop :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # varSamp :: WindowArg grp (null ty ': []) lat with db params from -> WindowFunction grp lat with db params from (Null (PGAvg ty)) Source # | |
FilterWhere (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) grp Source # | |
Defined in Squeal.PostgreSQL.Expression.Window | |
Generic (WindowArg grp args lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window | |
SListI args => RenderSQL (WindowArg grp args lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window Methods renderSQL :: WindowArg grp args lat with db params from -> ByteString Source # | |
type Rep (WindowArg grp args lat with db params from) Source # | |
Defined in Squeal.PostgreSQL.Expression.Window type Rep (WindowArg grp args lat with db params from) = D1 (MetaData "WindowArg" "Squeal.PostgreSQL.Expression.Window" "squeal-postgresql-0.6.0.1-2mcKKIXTe9UEFlpcl38Onr" False) (C1 (MetaCons "WindowArg" PrefixI True) (S1 (MetaSel (Just "windowArgs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NP (Expression grp lat with db params from) args)) :*: S1 (MetaSel (Just "windowFilter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Condition grp lat with db params from]))) |
pattern Window :: Expression grp lat with db params from arg -> WindowArg grp '[arg] lat with db params from Source #
Window
invokes a WindowFunction
on a single argument.
pattern Windows :: NP (Expression grp lat with db params from) args -> WindowArg grp args lat with db params from Source #
Windows
invokes a WindowFunction
on multiple argument.
Arguments
= WindowFunction grp lat with db params from x | cannot reference aliases |
A RankNType
for window functions with no arguments.
Arguments
= WindowArg grp '[x] lat with db params from | input |
-> WindowFunction grp lat with db params from y | output |
A RankNType
for window functions with 1 argument.
Arguments
= WindowArg grp xs lat with db params from | inputs |
-> WindowFunction grp lat with db 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.
Functions
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 :: NotNull PGint4 -#-> NotNull PGint4 Source #
integer ranging from 1 to the argument value, dividing the partition as equally as possible
>>>
printSQL $ ntile (Window 5)
ntile((5 :: int4))
lag :: '[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 :: '[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 :: ty -#-> ty Source #
returns value evaluated at the row that is the first row of the window frame
lastValue :: ty -#-> ty Source #
returns value evaluated at the row that is the last row of the window frame
nthValue :: '[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 -> x -#-> y Source #
escape hatch for defining window functions
unsafeWindowFunctionN :: SListI xs => ByteString -> xs --#-> y Source #
escape hatch for defining multi-argument window functions