SetOf ~> Set

This commit is contained in:
Eitan Chatav 2019-09-25 15:37:37 -07:00
parent b40c66b549
commit 5cc04695d5
5 changed files with 54 additions and 54 deletions

View File

@ -44,7 +44,7 @@ library
Squeal.PostgreSQL.Expression.Null
Squeal.PostgreSQL.Expression.Parameter
Squeal.PostgreSQL.Expression.Range
Squeal.PostgreSQL.Expression.SetOf
Squeal.PostgreSQL.Expression.Set
Squeal.PostgreSQL.Expression.Sort
Squeal.PostgreSQL.Expression.Subquery
Squeal.PostgreSQL.Expression.Text

View File

@ -214,7 +214,7 @@ import Squeal.PostgreSQL.Expression.Math as X
import Squeal.PostgreSQL.Expression.Null as X
import Squeal.PostgreSQL.Expression.Parameter as X
import Squeal.PostgreSQL.Expression.Range as X
import Squeal.PostgreSQL.Expression.SetOf as X
import Squeal.PostgreSQL.Expression.Set as X
import Squeal.PostgreSQL.Expression.Sort as X
import Squeal.PostgreSQL.Expression.Subquery as X
import Squeal.PostgreSQL.Expression.Text as X

View File

@ -42,7 +42,7 @@ import qualified Generics.SOP as SOP
import Squeal.PostgreSQL.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.SetOf
import Squeal.PostgreSQL.Expression.Set
import Squeal.PostgreSQL.List
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Schema
@ -123,8 +123,8 @@ index n expr = UnsafeExpression $
parenthesized (renderSQL expr) <> "[" <> fromString (show n) <> "]"
-- | Expand an array to a set of rows
unnest :: SetOfFunction "unnest" (null ('PGvararray ty)) '["unnest" ::: ty]
unnest = unsafeSetOfFunction
unnest :: SetFunction "unnest" (null ('PGvararray ty)) '["unnest" ::: ty]
unnest = unsafeSetFunction
-- | A row constructor is an expression that builds a row value
-- (also called a composite value) using values for its member fields.

View File

@ -81,7 +81,7 @@ import GHC.TypeLits
import Squeal.PostgreSQL.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.SetOf
import Squeal.PostgreSQL.Expression.Set
import Squeal.PostgreSQL.Expression.Type
import Squeal.PostgreSQL.List
import Squeal.PostgreSQL.Query
@ -337,9 +337,9 @@ jsonbPretty = unsafeFunction "jsonb_pretty"
>>> printSQL (select Star (from (jsonEach (literal (Json (object ["a" .= "foo", "b" .= "bar"]))))))
SELECT * FROM json_each(('{"a":"foo","b":"bar"}' :: json))
-}
jsonEach :: SetOfFunction "json_each" (null 'PGjson)
jsonEach :: SetFunction "json_each" (null 'PGjson)
'["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson]
jsonEach = unsafeSetOfFunction
jsonEach = unsafeSetFunction
{- | Expands the outermost binary JSON object into a set of key/value pairs.
@ -347,9 +347,9 @@ jsonEach = unsafeSetOfFunction
SELECT * FROM jsonb_each(('{"a":"foo","b":"bar"}' :: jsonb))
-}
jsonbEach
:: SetOfFunction "jsonb_each" (nullity 'PGjsonb)
:: SetFunction "jsonb_each" (nullity 'PGjsonb)
'["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson]
jsonbEach = unsafeSetOfFunction
jsonbEach = unsafeSetFunction
{- | Expands the outermost JSON object into a set of key/value pairs.
@ -357,9 +357,9 @@ jsonbEach = unsafeSetOfFunction
SELECT * FROM json_each_text(('{"a":"foo","b":"bar"}' :: json))
-}
jsonEachText
:: SetOfFunction "json_each_text" (null 'PGjson)
:: SetFunction "json_each_text" (null 'PGjson)
'["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext]
jsonEachText = unsafeSetOfFunction
jsonEachText = unsafeSetFunction
{- | Expands the outermost binary JSON object into a set of key/value pairs.
@ -367,9 +367,9 @@ jsonEachText = unsafeSetOfFunction
SELECT * FROM jsonb_each_text(('{"a":"foo","b":"bar"}' :: jsonb))
-}
jsonbEachText
:: SetOfFunction "jsonb_each_text" (null 'PGjsonb)
:: SetFunction "jsonb_each_text" (null 'PGjsonb)
'["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext]
jsonbEachText = unsafeSetOfFunction
jsonbEachText = unsafeSetFunction
{- | Returns set of keys in the outermost JSON object.
@ -377,9 +377,9 @@ jsonbEachText = unsafeSetOfFunction
json_object_keys(('{"a":"foo","b":"bar"}' :: json))
-}
jsonObjectKeys
:: SetOfFunction "json_object_keys" (nullity 'PGjson)
:: SetFunction "json_object_keys" (nullity 'PGjson)
'["json_object_keys" ::: 'NotNull 'PGtext]
jsonObjectKeys = unsafeSetOfFunction
jsonObjectKeys = unsafeSetFunction
{- | Returns set of keys in the outermost JSON object.
@ -387,9 +387,9 @@ jsonObjectKeys = unsafeSetOfFunction
jsonb_object_keys(('{"a":"foo","b":"bar"}' :: jsonb))
-}
jsonbObjectKeys
:: SetOfFunction "jsonb_object_keys" (null 'PGjsonb)
:: SetFunction "jsonb_object_keys" (null 'PGjsonb)
'["jsonb_object_keys" ::: 'NotNull 'PGtext]
jsonbObjectKeys = unsafeSetOfFunction
jsonbObjectKeys = unsafeSetFunction
-- | Build rows from Json types.
type JsonPopulateFunction fun json

View File

@ -1,5 +1,5 @@
{-|
Module: Squeal.PostgreSQL.Expression.SetOf
Module: Squeal.PostgreSQL.Expression.Set
Description: Set returning functions
Copyright: (c) Eitan Chatav, 2019
Maintainer: eitan@morphism.tech
@ -20,17 +20,17 @@ Set returning functions
, TypeOperators
#-}
module Squeal.PostgreSQL.Expression.SetOf
module Squeal.PostgreSQL.Expression.Set
( generateSeries
, generateSeriesStep
, generateSeriesTimestamp
, SetOfFunction
, unsafeSetOfFunction
, SetOfFunctionDB
, SetFunction
, unsafeSetFunction
, SetFunctionDB
, setOfFunction
, SetOfFunctionN
, unsafeSetOfFunctionN
, SetOfFunctionNDB
, SetFunctionN
, unsafeSetFunctionN
, SetFunctionNDB
, setOfFunctionN
) where
@ -48,65 +48,65 @@ import Squeal.PostgreSQL.Schema
{- |
A @RankNType@ for set returning functions with 1 argument.
-}
type SetOfFunction fun ty setof
type SetFunction fun ty row
= forall outer commons schemas params
. Expression outer commons 'Ungrouped schemas params '[] ty
-- ^ input
-> FromClause outer commons schemas params '[fun ::: setof]
-> FromClause outer commons schemas params '[fun ::: row]
-- ^ output
type SetOfFunctionDB fun schemas ty setof
type SetFunctionDB fun schemas ty row
= forall outer commons params
. Expression outer commons 'Ungrouped schemas params '[] ty
-- ^ input
-> FromClause outer commons schemas params '[fun ::: setof]
-> FromClause outer commons schemas params '[fun ::: row]
-- ^ output
-- | Escape hatch for a set returning function with 1 argument.
unsafeSetOfFunction
:: forall fun ty setof. KnownSymbol fun
=> SetOfFunction fun ty setof -- ^ set returning function
unsafeSetOfFunction x = UnsafeFromClause $
unsafeSetFunction
:: forall fun ty row. KnownSymbol fun
=> SetFunction fun ty row -- ^ set returning function
unsafeSetFunction x = UnsafeFromClause $
renderSymbol @fun <> parenthesized (renderSQL x)
setOfFunction
:: ( Has sch schemas schema
, Has fun schema ('Function ('[ty] :=> 'ReturnsTable setof)) )
, Has fun schema ('Function ('[ty] :=> 'ReturnsTable row)) )
=> QualifiedAlias sch fun
-> SetOfFunctionDB fun schemas ty setof
setOfFunction _ = unsafeSetOfFunction
-> SetFunctionDB fun schemas ty row
setOfFunction _ = unsafeSetFunction
{- |
A @RankNType@ for set returning functions with multiple argument.
-}
type SetOfFunctionN fun tys setof
type SetFunctionN fun tys row
= forall outer commons schemas params
. NP (Expression outer commons 'Ungrouped schemas params '[]) tys
-- ^ inputs
-> FromClause outer commons schemas params '[fun ::: setof]
-> FromClause outer commons schemas params '[fun ::: row]
-- ^ output
-- | Escape hatch for a set returning function with multiple argument.
unsafeSetOfFunctionN
:: forall fun tys setof. (SOP.SListI tys, KnownSymbol fun)
=> SetOfFunctionN fun tys setof -- ^ set returning function
unsafeSetOfFunctionN xs = UnsafeFromClause $
unsafeSetFunctionN
:: forall fun tys row. (SOP.SListI tys, KnownSymbol fun)
=> SetFunctionN fun tys row -- ^ set returning function
unsafeSetFunctionN xs = UnsafeFromClause $
renderSymbol @fun <> parenthesized (renderCommaSeparated renderSQL xs)
type SetOfFunctionNDB fun schemas tys setof
type SetFunctionNDB fun schemas tys row
= forall outer commons params
. NP (Expression outer commons 'Ungrouped schemas params '[]) tys
-- ^ inputs
-> FromClause outer commons schemas params '[fun ::: setof]
-> FromClause outer commons schemas params '[fun ::: row]
-- ^ output
setOfFunctionN
:: ( Has sch schemas schema
, Has fun schema ('Function (tys :=> 'ReturnsTable setof))
, Has fun schema ('Function (tys :=> 'ReturnsTable row))
, SOP.SListI tys )
=> QualifiedAlias sch fun
-> SetOfFunctionNDB fun schemas tys setof
setOfFunctionN _ = unsafeSetOfFunctionN
-> SetFunctionNDB fun schemas tys row
setOfFunctionN _ = unsafeSetFunctionN
{- | @generateSeries (start *: stop)@
@ -114,9 +114,9 @@ Generate a series of values, from @start@ to @stop@ with a step size of one
-}
generateSeries
:: ty `In` '[ 'PGint4, 'PGint8, 'PGnumeric]
=> SetOfFunctionN "generate_series" '[ null ty, null ty]
=> SetFunctionN "generate_series" '[ null ty, null ty]
'["generate_series" ::: null ty] -- ^ set returning function
generateSeries = unsafeSetOfFunctionN
generateSeries = unsafeSetFunctionN
{- | @generateSeries (start :* stop *: step)@
@ -124,9 +124,9 @@ Generate a series of values, from @start@ to @stop@ with a step size of @step@
-}
generateSeriesStep
:: ty `In` '[ 'PGint4, 'PGint8, 'PGnumeric]
=> SetOfFunctionN "generate_series" '[null ty, null ty, null ty]
=> SetFunctionN "generate_series" '[null ty, null ty, null ty]
'["generate_series" ::: null ty] -- ^ set returning function
generateSeriesStep = unsafeSetOfFunctionN
generateSeriesStep = unsafeSetFunctionN
{- | @generateSeries (start :* stop *: step)@
@ -134,6 +134,6 @@ Generate a series of values, from @start@ to @stop@ with a step size of @step@
-}
generateSeriesTimestamp
:: ty `In` '[ 'PGtimestamp, 'PGtimestamptz]
=> SetOfFunctionN "generate_series" '[null ty, null ty, null 'PGinterval]
=> SetFunctionN "generate_series" '[null ty, null ty, null 'PGinterval]
'["generate_series" ::: null ty] -- ^ set returning function
generateSeriesTimestamp = unsafeSetOfFunctionN
generateSeriesTimestamp = unsafeSetFunctionN