function changes

This commit is contained in:
Eitan Chatav 2019-09-25 13:53:52 -07:00
parent c42b09d1f3
commit 40ad89af29
15 changed files with 128 additions and 132 deletions

View File

@ -138,11 +138,11 @@ type Expr x
. Expression outer commons grp schemas params from x . Expression outer commons grp schemas params from x
``` ```
There is also a function type `(:-->)`, which is a subtype of the usual Haskell function There is also a function type `(-->)`, which is a subtype of the usual Haskell function
type `(->)`. type `(->)`.
```Haskell ```Haskell
type (:-->) x y type (-->) x y
= forall outer commons grp schemas params from = forall outer commons grp schemas params from
. Expression outer commons grp schemas params from x . Expression outer commons grp schemas params from x
-> Expression outer commons grp schemas params from y -> Expression outer commons grp schemas params from y

View File

@ -73,7 +73,7 @@ createFunction
-> NP (TypeExpression schemas) args -> NP (TypeExpression schemas) args
-> TypeExpression schemas ret -> TypeExpression schemas ret
-> FunctionDefinition schemas args ('Returns ret) -> FunctionDefinition schemas args ('Returns ret)
-> Definition schemas (Alter sch (Create fun ('Function (args '::--> 'Returns ret)) schema) schemas) -> Definition schemas (Alter sch (Create fun ('Function (args :=> 'Returns ret)) schema) schemas)
createFunction fun args ret fundef = UnsafeDefinition $ createFunction fun args ret fundef = UnsafeDefinition $
"CREATE" <+> "FUNCTION" <+> renderSQL fun "CREATE" <+> "FUNCTION" <+> renderSQL fun
<+> parenthesized (renderCommaSeparated renderSQL args) <+> parenthesized (renderCommaSeparated renderSQL args)
@ -87,7 +87,7 @@ createOrReplaceFunction
-> NP (TypeExpression schemas) args -> NP (TypeExpression schemas) args
-> TypeExpression schemas ret -> TypeExpression schemas ret
-> FunctionDefinition schemas args ('Returns ret) -> FunctionDefinition schemas args ('Returns ret)
-> Definition schemas (Alter sch (CreateOrReplace fun ('Function (args '::--> 'Returns ret)) schema) schemas) -> Definition schemas (Alter sch (CreateOrReplace fun ('Function (args :=> 'Returns ret)) schema) schemas)
createOrReplaceFunction fun args ret fundef = UnsafeDefinition $ createOrReplaceFunction fun args ret fundef = UnsafeDefinition $
"CREATE" <+> "OR" <+> "REPLACE" <+> "FUNCTION" <+> renderSQL fun "CREATE" <+> "OR" <+> "REPLACE" <+> "FUNCTION" <+> renderSQL fun
<+> parenthesized (renderCommaSeparated renderSQL args) <+> parenthesized (renderCommaSeparated renderSQL args)
@ -115,7 +115,7 @@ createSetFunction
-> NP (TypeExpression schemas) args -> NP (TypeExpression schemas) args
-> NP (Aliased (TypeExpression schemas)) rets -> NP (Aliased (TypeExpression schemas)) rets
-> FunctionDefinition schemas args ('ReturnsTable rets) -> FunctionDefinition schemas args ('ReturnsTable rets)
-> Definition schemas (Alter sch (Create fun ('Function (args '::--> 'ReturnsTable rets)) schema) schemas) -> Definition schemas (Alter sch (Create fun ('Function (args :=> 'ReturnsTable rets)) schema) schemas)
createSetFunction fun args rets fundef = UnsafeDefinition $ createSetFunction fun args rets fundef = UnsafeDefinition $
"CREATE" <+> "FUNCTION" <+> renderSQL fun "CREATE" <+> "FUNCTION" <+> renderSQL fun
<+> parenthesized (renderCommaSeparated renderSQL args) <+> parenthesized (renderCommaSeparated renderSQL args)
@ -128,14 +128,14 @@ createSetFunction fun args rets fundef = UnsafeDefinition $
createOrReplaceSetFunction createOrReplaceSetFunction
:: ( Has sch schemas schema :: ( Has sch schemas schema
, Has fun schema ('Function (args0 '::--> ret0)) , Has fun schema ('Function (args0 :=> ret0))
, SOP.SListI args , SOP.SListI args
, SOP.SListI rets ) , SOP.SListI rets )
=> QualifiedAlias sch fun => QualifiedAlias sch fun
-> NP (TypeExpression schemas) args -> NP (TypeExpression schemas) args
-> NP (Aliased (TypeExpression schemas)) rets -> NP (Aliased (TypeExpression schemas)) rets
-> FunctionDefinition schemas args ('ReturnsTable rets) -> FunctionDefinition schemas args ('ReturnsTable rets)
-> Definition schemas (Alter sch (CreateOrReplace fun ('Function (args '::--> 'ReturnsTable rets)) schema) schemas) -> Definition schemas (Alter sch (CreateOrReplace fun ('Function (args :=> 'ReturnsTable rets)) schema) schemas)
createOrReplaceSetFunction fun args rets fundef = UnsafeDefinition $ createOrReplaceSetFunction fun args rets fundef = UnsafeDefinition $
"CREATE" <+> "OR" <+> "REPLACE" <+> "FUNCTION" <+> renderSQL fun "CREATE" <+> "OR" <+> "REPLACE" <+> "FUNCTION" <+> renderSQL fun
<+> parenthesized (renderCommaSeparated renderSQL args) <+> parenthesized (renderCommaSeparated renderSQL args)
@ -149,9 +149,9 @@ createOrReplaceSetFunction fun args rets fundef = UnsafeDefinition $
createBinaryOp createBinaryOp
:: forall op fun sch schemas schema x y z. :: forall op fun sch schemas schema x y z.
( Has sch schemas schema ( Has sch schemas schema
, Has fun schema ('Function ('[x,y] '::--> 'Returns z)) , Has fun schema ('Function ('[x,y] :=> 'Returns z))
, KnownSymbol op ) , KnownSymbol op )
=> Alias fun => QualifiedAlias sch fun
-> TypeExpression schemas x -> TypeExpression schemas x
-> TypeExpression schemas y -> TypeExpression schemas y
-> Definition schemas -> Definition schemas
@ -168,9 +168,9 @@ createBinaryOp fun x y = UnsafeDefinition $
createLeftOp createLeftOp
:: forall op fun sch schemas schema x y. :: forall op fun sch schemas schema x y.
( Has sch schemas schema ( Has sch schemas schema
, Has fun schema ('Function ('[x] '::--> 'Returns y)) , Has fun schema ('Function ('[x] :=> 'Returns y))
, KnownSymbol op ) , KnownSymbol op )
=> Alias fun => QualifiedAlias sch fun
-> TypeExpression schemas x -> TypeExpression schemas x
-> Definition schemas -> Definition schemas
(Alter sch (Create op ('Operator ('LeftOp x y)) schema) schemas) (Alter sch (Create op ('Operator ('LeftOp x y)) schema) schemas)
@ -185,9 +185,9 @@ createLeftOp fun x = UnsafeDefinition $
createRightOp createRightOp
:: forall op fun sch schemas schema x y. :: forall op fun sch schemas schema x y.
( Has sch schemas schema ( Has sch schemas schema
, Has fun schema ('Function ('[x] '::--> 'Returns y)) , Has fun schema ('Function ('[x] :=> 'Returns y))
, KnownSymbol op ) , KnownSymbol op )
=> Alias fun => QualifiedAlias sch fun
-> TypeExpression schemas x -> TypeExpression schemas x
-> Definition schemas -> Definition schemas
(Alter sch (Create op ('Operator ('RightOp x y)) schema) schemas) (Alter sch (Create op ('Operator ('RightOp x y)) schema) schemas)

View File

@ -34,7 +34,7 @@ module Squeal.PostgreSQL.Expression
( -- * Expression ( -- * Expression
Expression (..) Expression (..)
, Expr , Expr
, (:-->) , type (-->)
, FunctionDB , FunctionDB
, unsafeFunction , unsafeFunction
, function , function
@ -48,7 +48,7 @@ module Squeal.PostgreSQL.Expression
, binaryOp , binaryOp
, FunctionVar , FunctionVar
, unsafeFunctionVar , unsafeFunctionVar
, FunctionN , type (--->)
, FunctionNDB , FunctionNDB
, unsafeFunctionN , unsafeFunctionN
, functionN , functionN
@ -159,7 +159,7 @@ type OperatorDB schemas x1 x2 y
-- This is a subtype of the usual Haskell function type `Prelude.->`, -- This is a subtype of the usual Haskell function type `Prelude.->`,
-- indeed a subcategory as it is closed under the usual -- indeed a subcategory as it is closed under the usual
-- `Prelude..` and `Prelude.id`. -- `Prelude..` and `Prelude.id`.
type (:-->) x y type (-->) x y
= forall outer commons grp schemas params from = forall outer commons grp schemas params from
. Expression outer commons grp schemas params from x . Expression outer commons grp schemas params from x
-- ^ input -- ^ input
@ -179,7 +179,7 @@ Use the `*:` operator to end your argument lists, like so.
>>> printSQL (unsafeFunctionN "fun" (true :* false :* localTime *: true)) >>> printSQL (unsafeFunctionN "fun" (true :* false :* localTime *: true))
fun(TRUE, FALSE, LOCALTIME, TRUE) fun(TRUE, FALSE, LOCALTIME, TRUE)
-} -}
type FunctionN xs y type (--->) xs y
= forall outer commons grp schemas params from = forall outer commons grp schemas params from
. NP (Expression outer commons grp schemas params from) xs . NP (Expression outer commons grp schemas params from) xs
-- ^ inputs -- ^ inputs
@ -327,7 +327,7 @@ binaryOp = unsafeBinaryOp $ renderSymbol @op
-- | >>> printSQL $ unsafeLeftOp "NOT" true -- | >>> printSQL $ unsafeLeftOp "NOT" true
-- (NOT TRUE) -- (NOT TRUE)
unsafeLeftOp :: ByteString -> x :--> y unsafeLeftOp :: ByteString -> x --> y
unsafeLeftOp op x = UnsafeExpression $ parenthesized $ op <+> renderSQL x unsafeLeftOp op x = UnsafeExpression $ parenthesized $ op <+> renderSQL x
leftOp leftOp
@ -339,7 +339,7 @@ leftOp = unsafeLeftOp $ renderSymbol @op
-- | >>> printSQL $ true & unsafeRightOp "IS NOT TRUE" -- | >>> printSQL $ true & unsafeRightOp "IS NOT TRUE"
-- (TRUE IS NOT TRUE) -- (TRUE IS NOT TRUE)
unsafeRightOp :: ByteString -> x :--> y unsafeRightOp :: ByteString -> x --> y
unsafeRightOp op x = UnsafeExpression $ parenthesized $ renderSQL x <+> op unsafeRightOp op x = UnsafeExpression $ parenthesized $ renderSQL x <+> op
rightOp rightOp
@ -351,25 +351,25 @@ rightOp = unsafeRightOp $ renderSymbol @op
-- | >>> printSQL $ unsafeFunction "f" true -- | >>> printSQL $ unsafeFunction "f" true
-- f(TRUE) -- f(TRUE)
unsafeFunction :: ByteString -> x :--> y unsafeFunction :: ByteString -> x --> y
unsafeFunction fun x = UnsafeExpression $ unsafeFunction fun x = UnsafeExpression $
fun <> parenthesized (renderSQL x) fun <> parenthesized (renderSQL x)
function function
:: (Has sch schemas schema, Has fun schema ('Function ('[x] '::--> 'Returns y))) :: (Has sch schemas schema, Has fun schema ('Function ('[x] :=> 'Returns y)))
=> QualifiedAlias sch fun => QualifiedAlias sch fun
-> FunctionDB schemas x y -> FunctionDB schemas x y
function = unsafeFunction . renderSQL function = unsafeFunction . renderSQL
-- | >>> printSQL $ unsafeFunctionN "f" (currentTime :* localTimestamp :* false *: literal 'a') -- | >>> printSQL $ unsafeFunctionN "f" (currentTime :* localTimestamp :* false *: literal 'a')
-- f(CURRENT_TIME, LOCALTIMESTAMP, FALSE, E'a') -- f(CURRENT_TIME, LOCALTIMESTAMP, FALSE, E'a')
unsafeFunctionN :: SListI xs => ByteString -> FunctionN xs y unsafeFunctionN :: SListI xs => ByteString -> xs ---> y
unsafeFunctionN fun xs = UnsafeExpression $ unsafeFunctionN fun xs = UnsafeExpression $
fun <> parenthesized (renderCommaSeparated renderSQL xs) fun <> parenthesized (renderCommaSeparated renderSQL xs)
functionN functionN
:: ( Has sch schemas schema :: ( Has sch schemas schema
, Has fun schema ('Function (xs '::--> 'Returns y)) , Has fun schema ('Function (xs :=> 'Returns y))
, SListI xs ) , SListI xs )
=> QualifiedAlias sch fun => QualifiedAlias sch fun
-> FunctionNDB schemas xs y -> FunctionNDB schemas xs y

View File

@ -111,14 +111,14 @@ array2 xss = UnsafeExpression $ "ARRAY" <>
-- | >>> printSQL $ cardinality (array [null_, false, true]) -- | >>> printSQL $ cardinality (array [null_, false, true])
-- cardinality(ARRAY[NULL, FALSE, TRUE]) -- cardinality(ARRAY[NULL, FALSE, TRUE])
cardinality :: null ('PGvararray ty) :--> null 'PGint8 cardinality :: null ('PGvararray ty) --> null 'PGint8
cardinality = unsafeFunction "cardinality" cardinality = unsafeFunction "cardinality"
-- | >>> printSQL $ array [null_, false, true] & index 2 -- | >>> printSQL $ array [null_, false, true] & index 2
-- (ARRAY[NULL, FALSE, TRUE])[2] -- (ARRAY[NULL, FALSE, TRUE])[2]
index index
:: Word64 -- ^ index :: Word64 -- ^ index
-> null ('PGvararray ty) :--> NullifyType ty -> null ('PGvararray ty) --> NullifyType ty
index n expr = UnsafeExpression $ index n expr = UnsafeExpression $
parenthesized (renderSQL expr) <> "[" <> fromString (show n) <> "]" parenthesized (renderSQL expr) <> "[" <> fromString (show n) <> "]"

View File

@ -162,7 +162,7 @@ isNotDistinctFrom = unsafeBinaryOp "IS NOT DISTINCT FROM"
>>> printSQL $ true & isTrue >>> printSQL $ true & isTrue
(TRUE IS TRUE) (TRUE IS TRUE)
-} -}
isTrue :: null0 'PGbool :--> null1 'PGbool isTrue :: null0 'PGbool --> null1 'PGbool
isTrue = unsafeRightOp "IS TRUE" isTrue = unsafeRightOp "IS TRUE"
{- | is false or unknown {- | is false or unknown
@ -170,7 +170,7 @@ isTrue = unsafeRightOp "IS TRUE"
>>> printSQL $ true & isNotTrue >>> printSQL $ true & isNotTrue
(TRUE IS NOT TRUE) (TRUE IS NOT TRUE)
-} -}
isNotTrue :: null0 'PGbool :--> null1 'PGbool isNotTrue :: null0 'PGbool --> null1 'PGbool
isNotTrue = unsafeRightOp "IS NOT TRUE" isNotTrue = unsafeRightOp "IS NOT TRUE"
{- | is false {- | is false
@ -178,7 +178,7 @@ isNotTrue = unsafeRightOp "IS NOT TRUE"
>>> printSQL $ true & isFalse >>> printSQL $ true & isFalse
(TRUE IS FALSE) (TRUE IS FALSE)
-} -}
isFalse :: null0 'PGbool :--> null1 'PGbool isFalse :: null0 'PGbool --> null1 'PGbool
isFalse = unsafeRightOp "IS FALSE" isFalse = unsafeRightOp "IS FALSE"
{- | is true or unknown {- | is true or unknown
@ -186,7 +186,7 @@ isFalse = unsafeRightOp "IS FALSE"
>>> printSQL $ true & isNotFalse >>> printSQL $ true & isNotFalse
(TRUE IS NOT FALSE) (TRUE IS NOT FALSE)
-} -}
isNotFalse :: null0 'PGbool :--> null1 'PGbool isNotFalse :: null0 'PGbool --> null1 'PGbool
isNotFalse = unsafeRightOp "IS NOT FALSE" isNotFalse = unsafeRightOp "IS NOT FALSE"
{- | is unknown {- | is unknown
@ -194,7 +194,7 @@ isNotFalse = unsafeRightOp "IS NOT FALSE"
>>> printSQL $ true & isUnknown >>> printSQL $ true & isUnknown
(TRUE IS UNKNOWN) (TRUE IS UNKNOWN)
-} -}
isUnknown :: null0 'PGbool :--> null1 'PGbool isUnknown :: null0 'PGbool --> null1 'PGbool
isUnknown = unsafeRightOp "IS UNKNOWN" isUnknown = unsafeRightOp "IS UNKNOWN"
{- | is true or false {- | is true or false
@ -202,5 +202,5 @@ isUnknown = unsafeRightOp "IS UNKNOWN"
>>> printSQL $ true & isNotUnknown >>> printSQL $ true & isNotUnknown
(TRUE IS NOT UNKNOWN) (TRUE IS NOT UNKNOWN)
-} -}
isNotUnknown :: null0 'PGbool :--> null1 'PGbool isNotUnknown :: null0 'PGbool --> null1 'PGbool
isNotUnknown = unsafeRightOp "IS NOT UNKNOWN" isNotUnknown = unsafeRightOp "IS NOT UNKNOWN"

View File

@ -188,7 +188,7 @@ Table 9.45: JSON creation functions
-- otherwise, a scalar value is produced. For any scalar type other than a -- otherwise, a scalar value is produced. For any scalar type other than a
-- number, a Boolean, or a null value, the text representation will be used, in -- number, a Boolean, or a null value, the text representation will be used, in
-- such a fashion that it is a valid json value. -- such a fashion that it is a valid json value.
toJson :: null ty :--> null 'PGjson toJson :: null ty --> null 'PGjson
toJson = unsafeFunction "to_json" toJson = unsafeFunction "to_json"
-- | Returns the value as jsonb. Arrays and composites are converted -- | Returns the value as jsonb. Arrays and composites are converted
@ -197,26 +197,26 @@ toJson = unsafeFunction "to_json"
-- otherwise, a scalar value is produced. For any scalar type other than a -- otherwise, a scalar value is produced. For any scalar type other than a
-- number, a Boolean, or a null value, the text representation will be used, in -- number, a Boolean, or a null value, the text representation will be used, in
-- such a fashion that it is a valid jsonb value. -- such a fashion that it is a valid jsonb value.
toJsonb :: null ty :--> null 'PGjsonb toJsonb :: null ty --> null 'PGjsonb
toJsonb = unsafeFunction "to_jsonb" toJsonb = unsafeFunction "to_jsonb"
-- | Returns the array as a JSON array. A PostgreSQL multidimensional array -- | Returns the array as a JSON array. A PostgreSQL multidimensional array
-- becomes a JSON array of arrays. -- becomes a JSON array of arrays.
arrayToJson :: null ('PGvararray ty) :--> null 'PGjson arrayToJson :: null ('PGvararray ty) --> null 'PGjson
arrayToJson = unsafeFunction "array_to_json" arrayToJson = unsafeFunction "array_to_json"
-- | Returns the row as a JSON object. -- | Returns the row as a JSON object.
rowToJson :: null ('PGcomposite ty) :--> null 'PGjson rowToJson :: null ('PGcomposite ty) --> null 'PGjson
rowToJson = unsafeFunction "row_to_json" rowToJson = unsafeFunction "row_to_json"
-- | Builds a possibly-heterogeneously-typed JSON array out of a variadic -- | Builds a possibly-heterogeneously-typed JSON array out of a variadic
-- argument list. -- argument list.
jsonBuildArray :: SOP.SListI tuple => FunctionN tuple (null 'PGjson) jsonBuildArray :: SOP.SListI tuple => tuple ---> null 'PGjson
jsonBuildArray = unsafeFunctionN "json_build_array" jsonBuildArray = unsafeFunctionN "json_build_array"
-- | Builds a possibly-heterogeneously-typed (binary) JSON array out of a -- | Builds a possibly-heterogeneously-typed (binary) JSON array out of a
-- variadic argument list. -- variadic argument list.
jsonbBuildArray :: SOP.SListI tuple => FunctionN tuple (null 'PGjsonb) jsonbBuildArray :: SOP.SListI tuple => tuple ---> null 'PGjsonb
jsonbBuildArray = unsafeFunctionN "jsonb_build_array" jsonbBuildArray = unsafeFunctionN "jsonb_build_array"
-- | Builds a possibly-heterogeneously-typed JSON object out of a variadic -- | Builds a possibly-heterogeneously-typed JSON object out of a variadic
@ -224,10 +224,10 @@ jsonbBuildArray = unsafeFunctionN "jsonb_build_array"
-- and values. -- and values.
class SOP.SListI tys => JsonBuildObject tys where class SOP.SListI tys => JsonBuildObject tys where
jsonBuildObject :: FunctionN tys (null 'PGjson) jsonBuildObject :: tys ---> null 'PGjson
jsonBuildObject = unsafeFunctionN "json_build_object" jsonBuildObject = unsafeFunctionN "json_build_object"
jsonbBuildObject :: FunctionN tys (null 'PGjsonb) jsonbBuildObject :: tys ---> null 'PGjsonb
jsonbBuildObject = unsafeFunctionN "jsonb_build_object" jsonbBuildObject = unsafeFunctionN "jsonb_build_object"
instance JsonBuildObject '[] instance JsonBuildObject '[]
@ -240,7 +240,7 @@ instance (JsonBuildObject tys, key `In` PGJsonKey)
-- which are taken as a key/value pair. -- which are taken as a key/value pair.
jsonObject jsonObject
:: null ('PGfixarray '[n,2] ('NotNull 'PGtext)) :: null ('PGfixarray '[n,2] ('NotNull 'PGtext))
:--> null 'PGjson --> null 'PGjson
jsonObject = unsafeFunction "json_object" jsonObject = unsafeFunction "json_object"
-- | Builds a binary JSON object out of a text array. -- | Builds a binary JSON object out of a text array.
@ -249,24 +249,24 @@ jsonObject = unsafeFunction "json_object"
-- which are taken as a key/value pair. -- which are taken as a key/value pair.
jsonbObject jsonbObject
:: null ('PGfixarray '[n,2] ('NotNull 'PGtext)) :: null ('PGfixarray '[n,2] ('NotNull 'PGtext))
:--> null 'PGjsonb --> null 'PGjsonb
jsonbObject = unsafeFunction "jsonb_object" jsonbObject = unsafeFunction "jsonb_object"
-- | This is an alternate form of 'jsonObject' that takes two arrays; one for -- | This is an alternate form of 'jsonObject' that takes two arrays; one for
-- keys and one for values, that are zipped pairwise to create a JSON object. -- keys and one for values, that are zipped pairwise to create a JSON object.
jsonZipObject :: FunctionN jsonZipObject ::
'[ null ('PGvararray ('NotNull 'PGtext)) '[ null ('PGvararray ('NotNull 'PGtext))
, null ('PGvararray ('NotNull 'PGtext)) ] , null ('PGvararray ('NotNull 'PGtext)) ]
( null 'PGjson ) ---> null 'PGjson
jsonZipObject = unsafeFunctionN "json_object" jsonZipObject = unsafeFunctionN "json_object"
-- | This is an alternate form of 'jsonbObject' that takes two arrays; one for -- | This is an alternate form of 'jsonbObject' that takes two arrays; one for
-- keys and one for values, that are zipped pairwise to create a binary JSON -- keys and one for values, that are zipped pairwise to create a binary JSON
-- object. -- object.
jsonbZipObject :: FunctionN jsonbZipObject ::
'[ null ('PGvararray ('NotNull 'PGtext)) '[ null ('PGvararray ('NotNull 'PGtext))
, null ('PGvararray ('NotNull 'PGtext)) ] , null ('PGvararray ('NotNull 'PGtext)) ]
( null 'PGjsonb ) ---> null 'PGjsonb
jsonbZipObject = unsafeFunctionN "jsonb_object" jsonbZipObject = unsafeFunctionN "jsonb_object"
{----------------------------------------- {-----------------------------------------
@ -274,31 +274,31 @@ Table 9.46: JSON processing functions
-----------------------------------------} -----------------------------------------}
-- | Returns the number of elements in the outermost JSON array. -- | Returns the number of elements in the outermost JSON array.
jsonArrayLength :: null 'PGjson :--> null 'PGint4 jsonArrayLength :: null 'PGjson --> null 'PGint4
jsonArrayLength = unsafeFunction "json_array_length" jsonArrayLength = unsafeFunction "json_array_length"
-- | Returns the number of elements in the outermost binary JSON array. -- | Returns the number of elements in the outermost binary JSON array.
jsonbArrayLength :: null 'PGjsonb :--> null 'PGint4 jsonbArrayLength :: null 'PGjsonb --> null 'PGint4
jsonbArrayLength = unsafeFunction "jsonb_array_length" jsonbArrayLength = unsafeFunction "jsonb_array_length"
-- | Returns the type of the outermost JSON value as a text string. Possible -- | Returns the type of the outermost JSON value as a text string. Possible
-- types are object, array, string, number, boolean, and null. -- types are object, array, string, number, boolean, and null.
jsonTypeof :: null 'PGjson :--> null 'PGtext jsonTypeof :: null 'PGjson --> null 'PGtext
jsonTypeof = unsafeFunction "json_typeof" jsonTypeof = unsafeFunction "json_typeof"
-- | Returns the type of the outermost binary JSON value as a text string. -- | Returns the type of the outermost binary JSON value as a text string.
-- Possible types are object, array, string, number, boolean, and null. -- Possible types are object, array, string, number, boolean, and null.
jsonbTypeof :: null 'PGjsonb :--> null 'PGtext jsonbTypeof :: null 'PGjsonb --> null 'PGtext
jsonbTypeof = unsafeFunction "jsonb_typeof" jsonbTypeof = unsafeFunction "jsonb_typeof"
-- | Returns its argument with all object fields that have null values omitted. -- | Returns its argument with all object fields that have null values omitted.
-- Other null values are untouched. -- Other null values are untouched.
jsonStripNulls :: null 'PGjson :--> null 'PGjson jsonStripNulls :: null 'PGjson --> null 'PGjson
jsonStripNulls = unsafeFunction "json_strip_nulls" jsonStripNulls = unsafeFunction "json_strip_nulls"
-- | Returns its argument with all object fields that have null values omitted. -- | Returns its argument with all object fields that have null values omitted.
-- Other null values are untouched. -- Other null values are untouched.
jsonbStripNulls :: null 'PGjsonb :--> null 'PGjsonb jsonbStripNulls :: null 'PGjsonb --> null 'PGjsonb
jsonbStripNulls = unsafeFunction "jsonb_strip_nulls" jsonbStripNulls = unsafeFunction "jsonb_strip_nulls"
-- | @ jsonbSet target path new_value create_missing @ -- | @ jsonbSet target path new_value create_missing @
@ -309,12 +309,9 @@ jsonbStripNulls = unsafeFunction "jsonb_strip_nulls"
-- item designated by path does not exist. As with the path orientated -- item designated by path does not exist. As with the path orientated
-- operators, negative integers that appear in path count from the end of JSON -- operators, negative integers that appear in path count from the end of JSON
-- arrays. -- arrays.
jsonbSet jsonbSet ::
:: FunctionN '[ null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext))
'[ null 'PGjsonb , null 'PGjsonb, null 'PGbool ] ---> null 'PGjsonb
, null ('PGvararray ('NotNull 'PGtext))
, null 'PGjsonb
, null 'PGbool ] (null 'PGjsonb)
jsonbSet = unsafeFunctionN "jsonbSet" jsonbSet = unsafeFunctionN "jsonbSet"
-- | @ jsonbInsert target path new_value insert_after @ -- | @ jsonbInsert target path new_value insert_after @
@ -326,19 +323,15 @@ jsonbSet = unsafeFunctionN "jsonbSet"
-- path is in JSONB object, @new_value@ will be inserted only if target does not -- path is in JSONB object, @new_value@ will be inserted only if target does not
-- exist. As with the path orientated operators, negative integers that appear -- exist. As with the path orientated operators, negative integers that appear
-- in path count from the end of JSON arrays. -- in path count from the end of JSON arrays.
jsonbInsert jsonbInsert ::
:: FunctionN '[ null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext))
'[ null 'PGjsonb , null 'PGjsonb, null 'PGbool ] ---> null 'PGjsonb
, null ('PGvararray ('NotNull 'PGtext))
, null 'PGjsonb
, null 'PGbool ] (null 'PGjsonb)
jsonbInsert = unsafeFunctionN "jsonb_insert" jsonbInsert = unsafeFunctionN "jsonb_insert"
-- | Returns its argument as indented JSON text. -- | Returns its argument as indented JSON text.
jsonbPretty :: null 'PGjsonb :--> null 'PGtext jsonbPretty :: null 'PGjsonb --> null 'PGtext
jsonbPretty = unsafeFunction "jsonb_pretty" jsonbPretty = unsafeFunction "jsonb_pretty"
{- | Expands the outermost JSON object into a set of key/value pairs. {- | Expands the outermost JSON object into a set of key/value pairs.
>>> printSQL (select Star (from (jsonEach (literal (Json (object ["a" .= "foo", "b" .= "bar"])))))) >>> printSQL (select Star (from (jsonEach (literal (Json (object ["a" .= "foo", "b" .= "bar"]))))))

View File

@ -47,7 +47,7 @@ false = UnsafeExpression "FALSE"
-- | >>> printSQL $ not_ true -- | >>> printSQL $ not_ true
-- (NOT TRUE) -- (NOT TRUE)
not_ :: null 'PGbool :--> null 'PGbool not_ :: null 'PGbool --> null 'PGbool
not_ = unsafeLeftOp "NOT" not_ = unsafeLeftOp "NOT"
-- | >>> printSQL $ true .&& false -- | >>> printSQL $ true .&& false

View File

@ -37,9 +37,7 @@ import Squeal.PostgreSQL.Schema
-- in printSQL expression -- in printSQL expression
-- :} -- :}
-- atan2(pi(), 2) -- atan2(pi(), 2)
atan2_ atan2_ :: float `In` PGFloating => '[ null float, null float] ---> null float
:: float `In` PGFloating
=> FunctionN '[ null float, null float] (null float)
atan2_ = unsafeFunctionN "atan2" atan2_ = unsafeFunctionN "atan2"
@ -78,7 +76,7 @@ rem_ = unsafeBinaryOp "%"
-- in printSQL expression -- in printSQL expression
-- :} -- :}
-- trunc(pi()) -- trunc(pi())
trunc :: frac `In` PGFloating => null frac :--> null frac trunc :: frac `In` PGFloating => null frac --> null frac
trunc = unsafeFunction "trunc" trunc = unsafeFunction "trunc"
-- | >>> :{ -- | >>> :{
@ -88,7 +86,7 @@ trunc = unsafeFunction "trunc"
-- in printSQL expression -- in printSQL expression
-- :} -- :}
-- round(pi()) -- round(pi())
round_ :: frac `In` PGFloating => null frac :--> null frac round_ :: frac `In` PGFloating => null frac --> null frac
round_ = unsafeFunction "round" round_ = unsafeFunction "round"
-- | >>> :{ -- | >>> :{
@ -98,5 +96,5 @@ round_ = unsafeFunction "round"
-- in printSQL expression -- in printSQL expression
-- :} -- :}
-- ceiling(pi()) -- ceiling(pi())
ceiling_ :: frac `In` PGFloating => null frac :--> null frac ceiling_ :: frac `In` PGFloating => null frac --> null frac
ceiling_ = unsafeFunction "ceiling" ceiling_ = unsafeFunction "ceiling"

View File

@ -44,7 +44,7 @@ null_ = UnsafeExpression "NULL"
-- --
-- >>> printSQL $ notNull true -- >>> printSQL $ notNull true
-- TRUE -- TRUE
notNull :: 'NotNull ty :--> 'Null ty notNull :: 'NotNull ty --> 'Null ty
notNull = UnsafeExpression . renderSQL notNull = UnsafeExpression . renderSQL
-- | return the leftmost value which is not NULL -- | return the leftmost value which is not NULL
@ -69,12 +69,12 @@ fromNull notNullx nullx = coalesce [nullx] notNullx
-- | >>> printSQL $ null_ & isNull -- | >>> printSQL $ null_ & isNull
-- NULL IS NULL -- NULL IS NULL
isNull :: 'Null ty :--> null 'PGbool isNull :: 'Null ty --> null 'PGbool
isNull x = UnsafeExpression $ renderSQL x <+> "IS NULL" isNull x = UnsafeExpression $ renderSQL x <+> "IS NULL"
-- | >>> printSQL $ null_ & isNotNull -- | >>> printSQL $ null_ & isNotNull
-- NULL IS NOT NULL -- NULL IS NOT NULL
isNotNull :: 'Null ty :--> null 'PGbool isNotNull :: 'Null ty --> null 'PGbool
isNotNull x = UnsafeExpression $ renderSQL x <+> "IS NOT NULL" isNotNull x = UnsafeExpression $ renderSQL x <+> "IS NOT NULL"
-- | analagous to `maybe` using @IS NULL@ -- | analagous to `maybe` using @IS NULL@
@ -100,5 +100,5 @@ matchNull y f x = ifThenElse (isNull x) y
>>> printSQL expr >>> printSQL expr
NULLIF(FALSE, ($1 :: bool)) NULLIF(FALSE, ($1 :: bool))
-} -}
nullIf :: FunctionN '[ 'NotNull ty, 'NotNull ty] ('Null ty) nullIf :: '[ 'NotNull ty, 'NotNull ty] ---> 'Null ty
nullIf = unsafeFunctionN "NULLIF" nullIf = unsafeFunctionN "NULLIF"

View File

@ -205,27 +205,26 @@ whole = NonEmpty Infinite Infinite
(@-) :: Operator (null ('PGrange ty)) (null ('PGrange ty)) (null ('PGrange ty)) (@-) :: Operator (null ('PGrange ty)) (null ('PGrange ty)) (null ('PGrange ty))
(@-) = unsafeBinaryOp "-" (@-) = unsafeBinaryOp "-"
lowerBound :: null ('PGrange ty) :--> 'Null ty lowerBound :: null ('PGrange ty) --> 'Null ty
lowerBound = unsafeFunction "lower" lowerBound = unsafeFunction "lower"
upperBound :: null ('PGrange ty) :--> 'Null ty upperBound :: null ('PGrange ty) --> 'Null ty
upperBound = unsafeFunction "upper" upperBound = unsafeFunction "upper"
isEmpty :: null ('PGrange ty) :--> 'Null 'PGbool isEmpty :: null ('PGrange ty) --> 'Null 'PGbool
isEmpty = unsafeFunction "isempty" isEmpty = unsafeFunction "isempty"
lowerInc :: null ('PGrange ty) :--> 'Null 'PGbool lowerInc :: null ('PGrange ty) --> 'Null 'PGbool
lowerInc = unsafeFunction "lower_inc" lowerInc = unsafeFunction "lower_inc"
lowerInf :: null ('PGrange ty) :--> 'Null 'PGbool lowerInf :: null ('PGrange ty) --> 'Null 'PGbool
lowerInf = unsafeFunction "lower_inf" lowerInf = unsafeFunction "lower_inf"
upperInc :: null ('PGrange ty) :--> 'Null 'PGbool upperInc :: null ('PGrange ty) --> 'Null 'PGbool
upperInc = unsafeFunction "upper_inc" upperInc = unsafeFunction "upper_inc"
upperInf :: null ('PGrange ty) :--> 'Null 'PGbool upperInf :: null ('PGrange ty) --> 'Null 'PGbool
upperInf = unsafeFunction "upper_inf" upperInf = unsafeFunction "upper_inf"
rangeMerge :: FunctionN rangeMerge :: '[null ('PGrange ty), null ('PGrange ty)] ---> null ('PGrange ty)
'[ null ('PGrange ty), null ('PGrange ty)] (null ('PGrange ty))
rangeMerge = unsafeFunctionN "range_merge" rangeMerge = unsafeFunctionN "range_merge"

View File

@ -26,9 +26,11 @@ module Squeal.PostgreSQL.Expression.SetOf
, generateSeriesTimestamp , generateSeriesTimestamp
, SetOfFunction , SetOfFunction
, unsafeSetOfFunction , unsafeSetOfFunction
, SetOfFunctionDB
, setOfFunction , setOfFunction
, SetOfFunctionN , SetOfFunctionN
, unsafeSetOfFunctionN , unsafeSetOfFunctionN
, SetOfFunctionNDB
, setOfFunctionN , setOfFunctionN
) where ) where
@ -53,6 +55,13 @@ type SetOfFunction fun ty setof
-> FromClause outer commons schemas params '[fun ::: setof] -> FromClause outer commons schemas params '[fun ::: setof]
-- ^ output -- ^ output
type SetOfFunctionDB fun schemas ty setof
= forall outer commons params
. Expression outer commons 'Ungrouped schemas params '[] ty
-- ^ input
-> FromClause outer commons schemas params '[fun ::: setof]
-- ^ output
-- | Escape hatch for a set returning function with 1 argument. -- | Escape hatch for a set returning function with 1 argument.
unsafeSetOfFunction unsafeSetOfFunction
:: forall fun ty setof. KnownSymbol fun :: forall fun ty setof. KnownSymbol fun
@ -62,11 +71,9 @@ unsafeSetOfFunction x = UnsafeFromClause $
setOfFunction setOfFunction
:: ( Has sch schemas schema :: ( Has sch schemas schema
, Has fun schema ('Function ('[ty] '::--> 'ReturnsTable setof)) ) , Has fun schema ('Function ('[ty] :=> 'ReturnsTable setof)) )
=> Alias fun => QualifiedAlias sch fun
-> ( forall outer commons params -> SetOfFunctionDB fun schemas ty setof
. Expression outer commons 'Ungrouped schemas params '[] ty
-> FromClause outer commons schemas params '[fun ::: setof] )
setOfFunction _ = unsafeSetOfFunction setOfFunction _ = unsafeSetOfFunction
{- | {- |
@ -86,14 +93,19 @@ unsafeSetOfFunctionN
unsafeSetOfFunctionN xs = UnsafeFromClause $ unsafeSetOfFunctionN xs = UnsafeFromClause $
renderSymbol @fun <> parenthesized (renderCommaSeparated renderSQL xs) renderSymbol @fun <> parenthesized (renderCommaSeparated renderSQL xs)
type SetOfFunctionNDB fun schemas tys setof
= forall outer commons params
. NP (Expression outer commons 'Ungrouped schemas params '[]) tys
-- ^ inputs
-> FromClause outer commons schemas params '[fun ::: setof]
-- ^ output
setOfFunctionN setOfFunctionN
:: ( Has sch schemas schema :: ( Has sch schemas schema
, Has fun schema ('Function (tys '::--> 'ReturnsTable setof)) , Has fun schema ('Function (tys :=> 'ReturnsTable setof))
, SOP.SListI tys ) , SOP.SListI tys )
=> Alias fun => QualifiedAlias sch fun
-> ( forall outer commons params -> SetOfFunctionNDB fun schemas tys setof
. NP (Expression outer commons 'Ungrouped schemas params '[]) tys
-> FromClause outer commons schemas params '[fun ::: setof] )
setOfFunctionN _ = unsafeSetOfFunctionN setOfFunctionN _ = unsafeSetOfFunctionN
{- | @generateSeries (start *: stop)@ {- | @generateSeries (start *: stop)@

View File

@ -30,17 +30,17 @@ import Squeal.PostgreSQL.Schema
-- | >>> printSQL $ lower "ARRRGGG" -- | >>> printSQL $ lower "ARRRGGG"
-- lower(E'ARRRGGG') -- lower(E'ARRRGGG')
lower :: null 'PGtext :--> null 'PGtext lower :: null 'PGtext --> null 'PGtext
lower = unsafeFunction "lower" lower = unsafeFunction "lower"
-- | >>> printSQL $ upper "eeee" -- | >>> printSQL $ upper "eeee"
-- upper(E'eeee') -- upper(E'eeee')
upper :: null 'PGtext :--> null 'PGtext upper :: null 'PGtext --> null 'PGtext
upper = unsafeFunction "upper" upper = unsafeFunction "upper"
-- | >>> printSQL $ charLength "four" -- | >>> printSQL $ charLength "four"
-- char_length(E'four') -- char_length(E'four')
charLength :: null 'PGtext :--> null 'PGint4 charLength :: null 'PGtext --> null 'PGint4
charLength = unsafeFunction "char_length" charLength = unsafeFunction "char_length"
-- | The `like` expression returns true if the @string@ matches -- | The `like` expression returns true if the @string@ matches

View File

@ -55,7 +55,7 @@ import Squeal.PostgreSQL.Schema
(.|) = unsafeBinaryOp "||" (.|) = unsafeBinaryOp "||"
-- | negate a `Squeal.PostgreSQL.Expression.Type.tsquery` -- | negate a `Squeal.PostgreSQL.Expression.Type.tsquery`
(.!) :: null 'PGtsquery :--> null 'PGtsquery (.!) :: null 'PGtsquery --> null 'PGtsquery
(.!) = unsafeLeftOp "!!" (.!) = unsafeLeftOp "!!"
-- | `Squeal.PostgreSQL.Expression.Type.tsquery` followed by -- | `Squeal.PostgreSQL.Expression.Type.tsquery` followed by
@ -66,51 +66,50 @@ import Squeal.PostgreSQL.Schema
-- | convert array of lexemes to `Squeal.PostgreSQL.Expression.Type.tsvector` -- | convert array of lexemes to `Squeal.PostgreSQL.Expression.Type.tsvector`
arrayToTSvector arrayToTSvector
:: null ('PGvararray ('NotNull 'PGtext)) :: null ('PGvararray ('NotNull 'PGtext))
:--> null 'PGtsvector --> null 'PGtsvector
arrayToTSvector = unsafeFunction "array_to_tsvector" arrayToTSvector = unsafeFunction "array_to_tsvector"
-- | number of lexemes in `Squeal.PostgreSQL.Expression.Type.tsvector` -- | number of lexemes in `Squeal.PostgreSQL.Expression.Type.tsvector`
tsvectorLength :: null 'PGtsvector :--> null 'PGint4 tsvectorLength :: null 'PGtsvector --> null 'PGint4
tsvectorLength = unsafeFunction "length" tsvectorLength = unsafeFunction "length"
-- | number of lexemes plus operators in `Squeal.PostgreSQL.Expression.Type.tsquery` -- | number of lexemes plus operators in `Squeal.PostgreSQL.Expression.Type.tsquery`
numnode :: null 'PGtsquery :--> null 'PGint4 numnode :: null 'PGtsquery --> null 'PGint4
numnode = unsafeFunction "numnode" numnode = unsafeFunction "numnode"
-- | produce `Squeal.PostgreSQL.Expression.Type.tsquery` ignoring punctuation -- | produce `Squeal.PostgreSQL.Expression.Type.tsquery` ignoring punctuation
plainToTSquery :: null 'PGtext :--> null 'PGtsquery plainToTSquery :: null 'PGtext --> null 'PGtsquery
plainToTSquery = unsafeFunction "plainto_tsquery" plainToTSquery = unsafeFunction "plainto_tsquery"
-- | produce `Squeal.PostgreSQL.Expression.Type.tsquery` that searches for a phrase, -- | produce `Squeal.PostgreSQL.Expression.Type.tsquery` that searches for a phrase,
-- ignoring punctuation -- ignoring punctuation
phraseToTSquery :: null 'PGtext :--> null 'PGtsquery phraseToTSquery :: null 'PGtext --> null 'PGtsquery
phraseToTSquery = unsafeFunction "phraseto_tsquery" phraseToTSquery = unsafeFunction "phraseto_tsquery"
-- | produce `Squeal.PostgreSQL.Expression.Type.tsquery` from a web search style query -- | produce `Squeal.PostgreSQL.Expression.Type.tsquery` from a web search style query
websearchToTSquery :: null 'PGtext :--> null 'PGtsquery websearchToTSquery :: null 'PGtext --> null 'PGtsquery
websearchToTSquery = unsafeFunction "websearch_to_tsquery" websearchToTSquery = unsafeFunction "websearch_to_tsquery"
-- | get indexable part of a `Squeal.PostgreSQL.Expression.Type.tsquery` -- | get indexable part of a `Squeal.PostgreSQL.Expression.Type.tsquery`
queryTree :: null 'PGtsquery :--> null 'PGtext queryTree :: null 'PGtsquery --> null 'PGtext
queryTree = unsafeFunction "query_tree" queryTree = unsafeFunction "query_tree"
-- | normalize words and convert to `Squeal.PostgreSQL.Expression.Type.tsquery` -- | normalize words and convert to `Squeal.PostgreSQL.Expression.Type.tsquery`
toTSquery :: null 'PGtext :--> null 'PGtsquery toTSquery :: null 'PGtext --> null 'PGtsquery
toTSquery = unsafeFunction "to_tsquery" toTSquery = unsafeFunction "to_tsquery"
-- | reduce document text to `Squeal.PostgreSQL.Expression.Type.tsvector` -- | reduce document text to `Squeal.PostgreSQL.Expression.Type.tsvector`
toTSvector toTSvector
:: ty `In` '[ 'PGtext, 'PGjson, 'PGjsonb] :: ty `In` '[ 'PGtext, 'PGjson, 'PGjsonb]
=> null ty :--> null 'PGtsvector => null ty --> null 'PGtsvector
toTSvector = unsafeFunction "to_tsvector" toTSvector = unsafeFunction "to_tsvector"
-- | assign weight to each element of `Squeal.PostgreSQL.Expression.Type.tsvector` -- | assign weight to each element of `Squeal.PostgreSQL.Expression.Type.tsvector`
setWeight setWeight :: '[null 'PGtsvector, null ('PGchar 1)] ---> null 'PGtsvector
:: FunctionN '[null 'PGtsvector, null ('PGchar 1)] (null 'PGtsvector)
setWeight = unsafeFunctionN "set_weight" setWeight = unsafeFunctionN "set_weight"
-- | remove positions and weights from `Squeal.PostgreSQL.Expression.Type.tsvector` -- | remove positions and weights from `Squeal.PostgreSQL.Expression.Type.tsvector`
strip :: null 'PGtsvector :--> null 'PGtsvector strip :: null 'PGtsvector --> null 'PGtsvector
strip = unsafeFunction "strip" strip = unsafeFunction "strip"
-- | @jsonToTSvector (document *: filter)@ -- | @jsonToTSvector (document *: filter)@
@ -123,7 +122,7 @@ strip = unsafeFunction "strip"
-- "boolean" (to include all Boolean values in the string format "true"/"false"), -- "boolean" (to include all Boolean values in the string format "true"/"false"),
-- "key" (to include all keys) or "all" (to include all above). -- "key" (to include all keys) or "all" (to include all above).
-- These values can be combined together to include, e.g. all string and numeric values. -- These values can be combined together to include, e.g. all string and numeric values.
jsonToTSvector :: FunctionN '[null 'PGjson, null 'PGjson] (null 'PGtsvector) jsonToTSvector :: '[null 'PGjson, null 'PGjson] ---> null 'PGtsvector
jsonToTSvector = unsafeFunctionN "json_to_tsvector" jsonToTSvector = unsafeFunctionN "json_to_tsvector"
-- | @jsonbToTSvector (document *: filter)@ -- | @jsonbToTSvector (document *: filter)@
@ -136,23 +135,23 @@ jsonToTSvector = unsafeFunctionN "json_to_tsvector"
-- "boolean" (to include all Boolean values in the string format "true"/"false"), -- "boolean" (to include all Boolean values in the string format "true"/"false"),
-- "key" (to include all keys) or "all" (to include all above). -- "key" (to include all keys) or "all" (to include all above).
-- These values can be combined together to include, e.g. all string and numeric values. -- These values can be combined together to include, e.g. all string and numeric values.
jsonbToTSvector :: FunctionN '[null 'PGjsonb, null 'PGjsonb] (null 'PGtsvector) jsonbToTSvector :: '[null 'PGjsonb, null 'PGjsonb] ---> null 'PGtsvector
jsonbToTSvector = unsafeFunctionN "jsonb_to_tsvector" jsonbToTSvector = unsafeFunctionN "jsonb_to_tsvector"
-- | remove given lexeme from `Squeal.PostgreSQL.Expression.Type.tsvector` -- | remove given lexeme from `Squeal.PostgreSQL.Expression.Type.tsvector`
tsDelete :: FunctionN tsDelete ::
'[null 'PGtsvector, null ('PGvararray ('NotNull 'PGtext))] '[null 'PGtsvector, null ('PGvararray ('NotNull 'PGtext))]
(null 'PGtsvector) ---> null 'PGtsvector
tsDelete = unsafeFunctionN "ts_delete" tsDelete = unsafeFunctionN "ts_delete"
-- | select only elements with given weights from `Squeal.PostgreSQL.Expression.Type.tsvector` -- | select only elements with given weights from `Squeal.PostgreSQL.Expression.Type.tsvector`
tsFilter :: FunctionN tsFilter ::
'[null 'PGtsvector, null ('PGvararray ('NotNull ('PGchar 1)))] '[null 'PGtsvector, null ('PGvararray ('NotNull ('PGchar 1)))]
(null 'PGtsvector) ---> null 'PGtsvector
tsFilter = unsafeFunctionN "ts_filter" tsFilter = unsafeFunctionN "ts_filter"
-- | display a `Squeal.PostgreSQL.Expression.Type.tsquery` match -- | display a `Squeal.PostgreSQL.Expression.Type.tsquery` match
tsHeadline tsHeadline
:: document `In` '[ 'PGtext, 'PGjson, 'PGjsonb] :: document `In` '[ 'PGtext, 'PGjson, 'PGjsonb]
=> FunctionN '[null document, null 'PGtsquery] (null 'PGtext) => '[null document, null 'PGtsquery] ---> null 'PGtext
tsHeadline = unsafeFunctionN "ts_headline" tsHeadline = unsafeFunctionN "ts_headline"

View File

@ -17,6 +17,7 @@ Date/Time functions and operators
, OverloadedStrings , OverloadedStrings
, PolyKinds , PolyKinds
, RankNTypes , RankNTypes
, TypeOperators
#-} #-}
module Squeal.PostgreSQL.Expression.Time module Squeal.PostgreSQL.Expression.Time
@ -85,9 +86,7 @@ Create date from year, month and day fields
>>> printSQL (makeDate (1984 :* 7 *: 3)) >>> printSQL (makeDate (1984 :* 7 *: 3))
make_date(1984, 7, 3) make_date(1984, 7, 3)
-} -}
makeDate :: FunctionN makeDate :: '[ null 'PGint4, null 'PGint4, null 'PGint4 ] ---> null 'PGdate
'[ null 'PGint4, null 'PGint4, null 'PGint4 ]
( null 'PGdate )
makeDate = unsafeFunctionN "make_date" makeDate = unsafeFunctionN "make_date"
{-| {-|
@ -96,9 +95,7 @@ Create time from hour, minute and seconds fields
>>> printSQL (makeTime (8 :* 15 *: 23.5)) >>> printSQL (makeTime (8 :* 15 *: 23.5))
make_time(8, 15, 23.5) make_time(8, 15, 23.5)
-} -}
makeTime :: FunctionN makeTime :: '[ null 'PGint4, null 'PGint4, null 'PGfloat8 ] ---> null 'PGtime
'[ null 'PGint4, null 'PGint4, null 'PGfloat8 ]
( null 'PGtime )
makeTime = unsafeFunctionN "make_time" makeTime = unsafeFunctionN "make_time"
{-| {-|
@ -107,10 +104,9 @@ Create timestamp from year, month, day, hour, minute and seconds fields
>>> printSQL (makeTimestamp (2013 :* 7 :* 15 :* 8 :* 15 *: 23.5)) >>> printSQL (makeTimestamp (2013 :* 7 :* 15 :* 8 :* 15 *: 23.5))
make_timestamp(2013, 7, 15, 8, 15, 23.5) make_timestamp(2013, 7, 15, 8, 15, 23.5)
-} -}
makeTimestamp :: FunctionN makeTimestamp ::
'[ null 'PGint4, null 'PGint4, null 'PGint4 '[ null 'PGint4, null 'PGint4, null 'PGint4
, null 'PGint4, null 'PGint4, null 'PGfloat8 ] , null 'PGint4, null 'PGint4, null 'PGfloat8 ] ---> null 'PGtimestamp
( null 'PGtimestamp )
makeTimestamp = unsafeFunctionN "make_timestamp" makeTimestamp = unsafeFunctionN "make_timestamp"
{-| {-|
@ -121,10 +117,9 @@ the current time zone is used
>>> printSQL (makeTimestamptz (2013 :* 7 :* 15 :* 8 :* 15 *: 23.5)) >>> printSQL (makeTimestamptz (2013 :* 7 :* 15 :* 8 :* 15 *: 23.5))
make_timestamptz(2013, 7, 15, 8, 15, 23.5) make_timestamptz(2013, 7, 15, 8, 15, 23.5)
-} -}
makeTimestamptz :: FunctionN makeTimestamptz ::
'[ null 'PGint4, null 'PGint4, null 'PGint4 '[ null 'PGint4, null 'PGint4, null 'PGint4
, null 'PGint4, null 'PGint4, null 'PGfloat8 ] , null 'PGint4, null 'PGint4, null 'PGfloat8 ] ---> null 'PGtimestamptz
( null 'PGtimestamptz )
makeTimestamptz = unsafeFunctionN "make_timestamptz" makeTimestamptz = unsafeFunctionN "make_timestamptz"
{-| {-|

View File

@ -45,7 +45,7 @@ module Squeal.PostgreSQL.Schema
, TableType , TableType
, SchemumType (..) , SchemumType (..)
, IndexType (..) , IndexType (..)
, FunctionType (..) , FunctionType
, OperatorType (..) , OperatorType (..)
, ReturnsType (..) , ReturnsType (..)
, SchemaType , SchemaType
@ -433,7 +433,7 @@ data SchemumType
| Operator OperatorType | Operator OperatorType
| UnsafeSchemum Symbol | UnsafeSchemum Symbol
data FunctionType = (::-->) [NullityType] ReturnsType type FunctionType = ([NullityType], ReturnsType)
data IndexType data IndexType
= Btree = Btree