Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
set returning functions
Synopsis
- type (-|->) arg set = forall db. SetFun db arg set
- type (--|->) arg set = forall db. SetFunN db arg set
- type SetFun db arg row = forall lat with params. Expression 'Ungrouped lat with db params '[] arg -> FromClause lat with db params '[row]
- type SetFunN db args set = forall lat with params. NP (Expression 'Ungrouped lat with db params '[]) args -> FromClause lat with db params '[set]
- generateSeries :: ty `In` '['PGint4, 'PGint8, 'PGnumeric] => '[null ty, null ty] --|-> ("generate_series" ::: '["generate_series" ::: null ty])
- generateSeriesStep :: ty `In` '['PGint4, 'PGint8, 'PGnumeric] => '[null ty, null ty, null ty] --|-> ("generate_series" ::: '["generate_series" ::: null ty])
- generateSeriesTimestamp :: ty `In` '['PGtimestamp, 'PGtimestamptz] => '[null ty, null ty, null 'PGinterval] --|-> ("generate_series" ::: '["generate_series" ::: null ty])
- unsafeSetFunction :: forall fun ty row. KnownSymbol fun => ByteString -> ty -|-> (fun ::: row)
- setFunction :: (Has sch db schema, Has fun schema ('Function ('[ty] :=> 'ReturnsTable row))) => QualifiedAlias sch fun -> SetFun db ty (fun ::: row)
- unsafeSetFunctionN :: forall fun tys row. (SListI tys, KnownSymbol fun) => ByteString -> tys --|-> (fun ::: row)
- setFunctionN :: (Has sch db schema, Has fun schema ('Function (tys :=> 'ReturnsTable row)), SListI tys) => QualifiedAlias sch fun -> SetFunN db tys (fun ::: row)
Set Functions
type (-|->) arg set = forall db. SetFun db arg set Source #
A RankNType
for set returning functions with 1 argument.
= forall db. SetFunN db arg set | output |
A RankNType
for set returning functions with multiple argument.
type SetFun db arg row Source #
= forall lat with params. Expression 'Ungrouped lat with db params '[] arg | input |
-> FromClause lat with db params '[row] | output |
Like -|->
but depends on the schemas of the database
type SetFunN db args set Source #
= forall lat with params. NP (Expression 'Ungrouped lat with db params '[]) args | input |
-> FromClause lat with db params '[set] | output |
Like --|->
but depends on the schemas of the database
:: ty `In` '['PGint4, 'PGint8, 'PGnumeric] | |
=> '[null ty, null ty] --|-> ("generate_series" ::: '["generate_series" ::: null ty]) | set returning function |
generateSeries (start :* stop)
Generate a series of values,
from start
to stop
with a step size of one
>>>
printSQL (generateSeries @'PGint4 (1 *: 10))
generate_series((1 :: int4), (10 :: int4))
:: ty `In` '['PGint4, 'PGint8, 'PGnumeric] | |
=> '[null ty, null ty, null ty] --|-> ("generate_series" ::: '["generate_series" ::: null ty]) | set returning function |
generateSeriesStep (start :* stop *: step)
Generate a series of values,
from start
to stop
with a step size of step
>>>
printSQL (generateSeriesStep @'PGint8 (2 :* 100 *: 2))
generate_series((2 :: int8), (100 :: int8), (2 :: int8))
generateSeriesTimestamp Source #
:: ty `In` '['PGtimestamp, 'PGtimestamptz] | |
=> '[null ty, null ty, null 'PGinterval] --|-> ("generate_series" ::: '["generate_series" ::: null ty]) | set returning function |
generateSeriesTimestamp (start :* stop *: step)
Generate a series of timestamps,
from start
to stop
with a step size of step
>>>
:{
let start = now stop = now !+ interval_ 10 Years step = interval_ 1 Months in printSQL (generateSeriesTimestamp (start :* stop *: step)) :} generate_series(now(), (now() + (INTERVAL '10.000 years')), (INTERVAL '1.000 months'))
:: forall fun ty row. KnownSymbol fun | |
=> ByteString | |
-> ty -|-> (fun ::: row) | set returning function |
Escape hatch for a set returning function of a single variable
:: (Has sch db schema, Has fun schema ('Function ('[ty] :=> 'ReturnsTable row))) | |
=> QualifiedAlias sch fun | function alias |
-> SetFun db ty (fun ::: row) |
Call a user defined set returning function of a single variable
>>>
type Fn = '[ 'Null 'PGbool] :=> 'ReturnsTable '["ret" ::: 'NotNull 'PGnumeric]
>>>
type Schema = '["fn" ::: 'Function Fn]
>>>
:{
let fn :: SetFun (Public Schema) ('Null 'PGbool) ("fn" ::: '["ret" ::: 'NotNull 'PGnumeric]) fn = setFunction #fn in printSQL (fn true) :} "fn"(TRUE)
:: forall fun tys row. (SListI tys, KnownSymbol fun) | |
=> ByteString | |
-> tys --|-> (fun ::: row) | set returning function |
Escape hatch for a multivariable set returning function
:: (Has sch db schema, Has fun schema ('Function (tys :=> 'ReturnsTable row)), SListI tys) | |
=> QualifiedAlias sch fun | function alias |
-> SetFunN db tys (fun ::: row) |
Call a user defined multivariable set returning function
>>>
type Fn = '[ 'Null 'PGbool, 'Null 'PGtext] :=> 'ReturnsTable '["ret" ::: 'NotNull 'PGnumeric]
>>>
type Schema = '["fn" ::: 'Function Fn]
>>>
:{
let fn :: SetFunN (Public Schema) '[ 'Null 'PGbool, 'Null 'PGtext] ("fn" ::: '["ret" ::: 'NotNull 'PGnumeric]) fn = setFunctionN #fn in printSQL (fn (true *: "hi")) :} "fn"(TRUE, (E'hi' :: text))