squeal-postgresql-0.9.0.0: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Expression.Window

Description

window functions, arguments and definitions

Synopsis

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

Instances details
OrderBy (WindowDefinition grp) grp Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

orderBy :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType). [SortExpression grp lat with db params from] -> WindowDefinition grp lat with db params from -> WindowDefinition grp lat with db params from Source #

RenderSQL (WindowDefinition grp lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

renderSQL :: WindowDefinition grp lat with db params from -> ByteString Source #

partitionBy 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.

Instances

Instances details
Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowFunction grp lat with db params from ('NotNull 'PGint8) Source #

count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('NotNull 'PGint8) Source #

sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGSum ty)) Source #

arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ('PGvararray ty)) Source #

jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjson) Source #

jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjsonb) Source #

bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source #

bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source #

boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source #

min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source #

avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGint8) Source #

regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). 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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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 # 
Instance details

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.9.0.0-D17NIjlcsGRAwJTaCTXyvM" '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 #

WindowArgs are used for the input of WindowFunctions.

Constructors

WindowArg 

Fields

Instances

Instances details
Aggregate (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) (WindowFunction grp :: FromType -> FromType -> SchemasType -> [NullType] -> FromType -> NullType -> Type) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

countStar :: forall (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowFunction grp lat with db params from ('NotNull 'PGint8) Source #

count :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('NotNull 'PGint8) Source #

sum_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGSum ty)) Source #

arrayAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ('PGvararray ty)) Source #

jsonAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjson) Source #

jsonbAgg :: forall (ty :: NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[ty] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGjsonb) Source #

bitAnd :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source #

bitOr :: forall (int :: PGType) (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). In int PGIntegral => WindowArg grp '[null int] lat with db params from -> WindowFunction grp lat with db params from ('Null int) Source #

boolAnd :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

boolOr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

every :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGbool] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGbool) Source #

max_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source #

min_ :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null ty) Source #

avg :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

corr :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

covarPop :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

covarSamp :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrAvgX :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrAvgY :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrCount :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGint8) Source #

regrIntercept :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrR2 :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSlope :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSxx :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSxy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

regrSyy :: forall (null :: PGType -> NullType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null 'PGfloat8, null 'PGfloat8] lat with db params from -> WindowFunction grp lat with db params from ('Null 'PGfloat8) Source #

stddev :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

stddevPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

stddevSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

variance :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

varPop :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

varSamp :: forall (null :: PGType -> NullType) (ty :: PGType) (lat :: k) (with :: k) (db :: k) (params :: k) (from :: k). WindowArg grp '[null ty] lat with db params from -> WindowFunction grp lat with db params from ('Null (PGAvg ty)) Source #

(Has tab (Join from lat) row, Has col row ty, GroupedBy tab col bys) => IsQualified tab col (WindowArg ('Grouped bys) '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

(!) :: Alias tab -> Alias col -> WindowArg ('Grouped bys) '[ty] lat with db params from Source #

(Has tab (Join from lat) row, Has col row ty) => IsQualified tab col (WindowArg 'Ungrouped '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

(!) :: Alias tab -> Alias col -> WindowArg 'Ungrouped '[ty] lat with db params from Source #

(HasUnique tab (Join from lat) row, Has col row ty, GroupedBy tab col bys) => IsLabel col (WindowArg ('Grouped bys) '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

fromLabel :: WindowArg ('Grouped bys) '[ty] lat with db params from #

(HasUnique tab (Join from lat) row, Has col row ty) => IsLabel col (WindowArg 'Ungrouped '[ty] lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

fromLabel :: WindowArg 'Ungrouped '[ty] lat with db params from #

FilterWhere (WindowArg grp :: [NullType] -> FromType -> FromType -> SchemasType -> [NullType] -> FromType -> Type) grp Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Methods

filterWhere :: forall (lat :: FromType) (with :: FromType) (db :: SchemasType) (params :: [NullType]) (from :: FromType) (xs :: k). Condition grp lat with db params from -> WindowArg grp xs lat with db params from -> WindowArg grp xs lat with db params from Source #

Generic (WindowArg grp args lat with db params from) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Window

Associated Types

type Rep (WindowArg grp args lat with db params from) :: Type -> Type #

Methods

from :: WindowArg grp args lat with db params from -> Rep (WindowArg grp args lat with db params from) x #

to :: Rep (WindowArg grp args lat with db params from) x -> WindowArg grp args lat with db params from #

SListI args => RenderSQL (WindowArg grp args lat with db params from) Source # 
Instance details

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 # 
Instance details

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.9.0.0-D17NIjlcsGRAwJTaCTXyvM" '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 Source #

Arguments

:: Expression grp lat with db params from arg

argument

-> WindowArg grp '[arg] lat with db params from 

Window invokes a WindowFunction on a single argument.

pattern Windows Source #

Arguments

:: NP (Expression grp lat with db params from) args

arguments

-> WindowArg grp args lat with db params from 

Windows invokes a WindowFunction on multiple argument.

type WinFun0 x Source #

Arguments

 = forall grp lat with db params from. WindowFunction grp lat with db params from x

cannot reference aliases

A RankNType for window functions with no arguments.

type (-#->) x y Source #

Arguments

 = forall grp lat with db params from. 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.

type (--#->) xs y Source #

Arguments

 = forall grp lat with db params from. 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