{-# LANGUAGE
DataKinds
, FlexibleContexts
, FlexibleInstances
, GADTs
, OverloadedLabels
, OverloadedStrings
, PolyKinds
, RankNTypes
, ScopedTypeVariables
, TypeApplications
, TypeOperators
, UndecidableInstances
, UndecidableSuperClasses
#-}
module Squeal.PostgreSQL.Expression.Json
(
(.->)
, (.->>)
, (.#>)
, (.#>>)
, (.?)
, (.?|)
, (.?&)
, (.-.)
, (#-.)
, toJson
, toJsonb
, arrayToJson
, rowToJson
, jsonBuildArray
, jsonbBuildArray
, JsonBuildObject (..)
, jsonObject
, jsonbObject
, jsonZipObject
, jsonbZipObject
, jsonArrayLength
, jsonbArrayLength
, jsonTypeof
, jsonbTypeof
, jsonStripNulls
, jsonbStripNulls
, jsonbSet
, jsonbInsert
, jsonbPretty
, jsonEach
, jsonbEach
, jsonEachText
, jsonArrayElementsText
, jsonbEachText
, jsonbArrayElementsText
, jsonObjectKeys
, jsonbObjectKeys
, JsonPopulateFunction
, jsonPopulateRecord
, jsonbPopulateRecord
, jsonPopulateRecordSet
, jsonbPopulateRecordSet
, JsonToRecordFunction
, jsonToRecord
, jsonbToRecord
, jsonToRecordSet
, jsonbToRecordSet
) where
import Data.ByteString (ByteString)
import GHC.TypeLits
import Squeal.PostgreSQL.Type.Alias
import Squeal.PostgreSQL.Expression
import Squeal.PostgreSQL.Expression.Type
import Squeal.PostgreSQL.Type.List
import Squeal.PostgreSQL.Query.From
import Squeal.PostgreSQL.Query.From.Set
import Squeal.PostgreSQL.Render
import Squeal.PostgreSQL.Type.Schema
import qualified Generics.SOP as SOP
(.->)
:: (json `In` PGJsonType, key `In` PGJsonKey)
=> Operator (null json) (null key) ('Null json)
infixl 8 .->
.-> :: Operator (null json) (null key) ('Null json)
(.->) = ByteString -> Operator (null json) (null key) ('Null json)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"->"
(.->>)
:: (json `In` PGJsonType, key `In` PGJsonKey)
=> Operator (null json) (null key) ('Null 'PGtext)
infixl 8 .->>
.->> :: Operator (null json) (null key) ('Null 'PGtext)
(.->>) = ByteString -> Operator (null json) (null key) ('Null 'PGtext)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"->>"
(.#>)
:: json `In` PGJsonType
=> Operator (null json) (null ('PGvararray ('NotNull 'PGtext))) ('Null json)
infixl 8 .#>
.#> :: Operator
(null json) (null ('PGvararray ('NotNull 'PGtext))) ('Null json)
(.#>) = ByteString
-> Operator
(null json) (null ('PGvararray ('NotNull 'PGtext))) ('Null json)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"#>"
(.#>>)
:: json `In` PGJsonType
=> Operator (null json) (null ('PGvararray ('NotNull 'PGtext))) ('Null 'PGtext)
infixl 8 .#>>
.#>> :: Operator
(null json) (null ('PGvararray ('NotNull 'PGtext))) ('Null 'PGtext)
(.#>>) = ByteString
-> Operator
(null json) (null ('PGvararray ('NotNull 'PGtext))) ('Null 'PGtext)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"#>>"
(.?) :: Operator (null 'PGjsonb) (null 'PGtext) ('Null 'PGbool)
infixl 9 .?
.? :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression grp lat with db params from (null 'PGtext)
-> Expression grp lat with db params from ('Null 'PGbool)
(.?) = ByteString
-> Operator (null 'PGjsonb) (null 'PGtext) ('Null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"?"
(.?|) :: Operator
(null 'PGjsonb)
(null ('PGvararray ('NotNull 'PGtext)))
('Null 'PGbool)
infixl 9 .?|
.?| :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression
grp lat with db params from (null ('PGvararray ('NotNull 'PGtext)))
-> Expression grp lat with db params from ('Null 'PGbool)
(.?|) = ByteString
-> Operator
(null 'PGjsonb)
(null ('PGvararray ('NotNull 'PGtext)))
('Null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"?|"
(.?&) :: Operator
(null 'PGjsonb)
(null ('PGvararray ('NotNull 'PGtext)))
('Null 'PGbool)
infixl 9 .?&
.?& :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression
grp lat with db params from (null ('PGvararray ('NotNull 'PGtext)))
-> Expression grp lat with db params from ('Null 'PGbool)
(.?&) = ByteString
-> Operator
(null 'PGjsonb)
(null ('PGvararray ('NotNull 'PGtext)))
('Null 'PGbool)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"?&"
(.-.)
:: key `In` '[ 'PGtext, 'PGvararray ('NotNull 'PGtext), 'PGint4, 'PGint2 ]
=> Operator (null 'PGjsonb) (null key) (null 'PGjsonb)
infixl 6 .-.
.-. :: Operator (null 'PGjsonb) (null key) (null 'PGjsonb)
(.-.) = ByteString -> Operator (null 'PGjsonb) (null key) (null 'PGjsonb)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"-"
(#-.) :: Operator (null 'PGjsonb) (null ('PGvararray ('NotNull 'PGtext))) (null 'PGjsonb)
infixl 6 #-.
#-. :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression
grp lat with db params from (null ('PGvararray ('NotNull 'PGtext)))
-> Expression grp lat with db params from (null 'PGjsonb)
(#-.) = ByteString
-> Operator
(null 'PGjsonb)
(null ('PGvararray ('NotNull 'PGtext)))
(null 'PGjsonb)
forall (ty0 :: NullType) (ty1 :: NullType) (ty2 :: NullType).
ByteString -> Operator ty0 ty1 ty2
unsafeBinaryOp ByteString
"#-"
toJson :: null ty --> null 'PGjson
toJson :: Expression grp lat with db params from (null ty)
-> Expression grp lat with db params from (null 'PGjson)
toJson = ByteString -> null ty --> null 'PGjson
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"to_json"
toJsonb :: null ty --> null 'PGjsonb
toJsonb :: Expression grp lat with db params from (null ty)
-> Expression grp lat with db params from (null 'PGjsonb)
toJsonb = ByteString -> null ty --> null 'PGjsonb
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"to_jsonb"
arrayToJson :: null ('PGvararray ty) --> null 'PGjson
arrayToJson :: Expression grp lat with db params from (null ('PGvararray ty))
-> Expression grp lat with db params from (null 'PGjson)
arrayToJson = ByteString -> null ('PGvararray ty) --> null 'PGjson
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"array_to_json"
rowToJson :: null ('PGcomposite ty) --> null 'PGjson
rowToJson :: Expression grp lat with db params from (null ('PGcomposite ty))
-> Expression grp lat with db params from (null 'PGjson)
rowToJson = ByteString -> null ('PGcomposite ty) --> null 'PGjson
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"row_to_json"
jsonBuildArray :: SOP.SListI tuple => tuple ---> null 'PGjson
jsonBuildArray :: tuple ---> null 'PGjson
jsonBuildArray = ByteString -> tuple ---> null 'PGjson
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"json_build_array"
jsonbBuildArray :: SOP.SListI tuple => tuple ---> null 'PGjsonb
jsonbBuildArray :: tuple ---> null 'PGjsonb
jsonbBuildArray = ByteString -> tuple ---> null 'PGjsonb
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"jsonb_build_array"
class SOP.SListI tys => JsonBuildObject tys where
jsonBuildObject :: tys ---> null 'PGjson
jsonBuildObject = ByteString -> tys ---> null 'PGjson
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"json_build_object"
jsonbBuildObject :: tys ---> null 'PGjsonb
jsonbBuildObject = ByteString -> tys ---> null 'PGjsonb
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"jsonb_build_object"
instance JsonBuildObject '[]
instance (JsonBuildObject tys, key `In` PGJsonKey)
=> JsonBuildObject ('NotNull key ': value ': tys)
jsonObject
:: null ('PGfixarray '[n,2] ('NotNull 'PGtext))
--> null 'PGjson
jsonObject :: Expression
grp
lat
with
db
params
from
(null ('PGfixarray '[n, 2] ('NotNull 'PGtext)))
-> Expression grp lat with db params from (null 'PGjson)
jsonObject = ByteString
-> null ('PGfixarray '[n, 2] ('NotNull 'PGtext)) --> null 'PGjson
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"json_object"
jsonbObject
:: null ('PGfixarray '[n,2] ('NotNull 'PGtext))
--> null 'PGjsonb
jsonbObject :: Expression
grp
lat
with
db
params
from
(null ('PGfixarray '[n, 2] ('NotNull 'PGtext)))
-> Expression grp lat with db params from (null 'PGjsonb)
jsonbObject = ByteString
-> null ('PGfixarray '[n, 2] ('NotNull 'PGtext)) --> null 'PGjsonb
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"jsonb_object"
jsonZipObject ::
'[ null ('PGvararray ('NotNull 'PGtext))
, null ('PGvararray ('NotNull 'PGtext)) ]
---> null 'PGjson
jsonZipObject :: NP
(Expression grp lat with db params from)
'[null ('PGvararray ('NotNull 'PGtext)),
null ('PGvararray ('NotNull 'PGtext))]
-> Expression grp lat with db params from (null 'PGjson)
jsonZipObject = ByteString
-> '[null ('PGvararray ('NotNull 'PGtext)),
null ('PGvararray ('NotNull 'PGtext))]
---> null 'PGjson
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"json_object"
jsonbZipObject ::
'[ null ('PGvararray ('NotNull 'PGtext))
, null ('PGvararray ('NotNull 'PGtext)) ]
---> null 'PGjsonb
jsonbZipObject :: NP
(Expression grp lat with db params from)
'[null ('PGvararray ('NotNull 'PGtext)),
null ('PGvararray ('NotNull 'PGtext))]
-> Expression grp lat with db params from (null 'PGjsonb)
jsonbZipObject = ByteString
-> '[null ('PGvararray ('NotNull 'PGtext)),
null ('PGvararray ('NotNull 'PGtext))]
---> null 'PGjsonb
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"jsonb_object"
jsonArrayLength :: null 'PGjson --> null 'PGint4
jsonArrayLength :: Expression grp lat with db params from (null 'PGjson)
-> Expression grp lat with db params from (null 'PGint4)
jsonArrayLength = ByteString -> null 'PGjson --> null 'PGint4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"json_array_length"
jsonbArrayLength :: null 'PGjsonb --> null 'PGint4
jsonbArrayLength :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression grp lat with db params from (null 'PGint4)
jsonbArrayLength = ByteString -> null 'PGjsonb --> null 'PGint4
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"jsonb_array_length"
jsonTypeof :: null 'PGjson --> null 'PGtext
jsonTypeof :: Expression grp lat with db params from (null 'PGjson)
-> Expression grp lat with db params from (null 'PGtext)
jsonTypeof = ByteString -> null 'PGjson --> null 'PGtext
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"json_typeof"
jsonbTypeof :: null 'PGjsonb --> null 'PGtext
jsonbTypeof :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression grp lat with db params from (null 'PGtext)
jsonbTypeof = ByteString -> null 'PGjsonb --> null 'PGtext
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"jsonb_typeof"
jsonStripNulls :: null 'PGjson --> null 'PGjson
jsonStripNulls :: Expression grp lat with db params from (null 'PGjson)
-> Expression grp lat with db params from (null 'PGjson)
jsonStripNulls = ByteString -> null 'PGjson --> null 'PGjson
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"json_strip_nulls"
jsonbStripNulls :: null 'PGjsonb --> null 'PGjsonb
jsonbStripNulls :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression grp lat with db params from (null 'PGjsonb)
jsonbStripNulls = ByteString -> null 'PGjsonb --> null 'PGjsonb
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"jsonb_strip_nulls"
jsonbSet ::
'[ null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext))
, null 'PGjsonb, null 'PGbool ] ---> null 'PGjsonb
jsonbSet :: NP
(Expression grp lat with db params from)
'[null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext)),
null 'PGjsonb, null 'PGbool]
-> Expression grp lat with db params from (null 'PGjsonb)
jsonbSet = ByteString
-> '[null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext)),
null 'PGjsonb, null 'PGbool]
---> null 'PGjsonb
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"jsonbSet"
jsonbInsert ::
'[ null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext))
, null 'PGjsonb, null 'PGbool ] ---> null 'PGjsonb
jsonbInsert :: NP
(Expression grp lat with db params from)
'[null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext)),
null 'PGjsonb, null 'PGbool]
-> Expression grp lat with db params from (null 'PGjsonb)
jsonbInsert = ByteString
-> '[null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext)),
null 'PGjsonb, null 'PGbool]
---> null 'PGjsonb
forall (xs :: [NullType]) (y :: NullType).
SListI xs =>
ByteString -> xs ---> y
unsafeFunctionN ByteString
"jsonb_insert"
jsonbPretty :: null 'PGjsonb --> null 'PGtext
jsonbPretty :: Expression grp lat with db params from (null 'PGjsonb)
-> Expression grp lat with db params from (null 'PGtext)
jsonbPretty = ByteString -> null 'PGjsonb --> null 'PGtext
forall (x :: NullType) (y :: NullType). ByteString -> x --> y
unsafeFunction ByteString
"jsonb_pretty"
jsonEach :: null 'PGjson -|->
("json_each" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson])
jsonEach :: Expression 'Ungrouped lat with db params '[] (null 'PGjson)
-> FromClause
lat
with
db
params
'["json_each"
::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson]]
jsonEach = ByteString
-> null 'PGjson
-|-> ("json_each"
::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson])
forall (fun :: Symbol) (ty :: NullType) (row :: RowType).
KnownSymbol fun =>
ByteString -> ty -|-> (fun ::: row)
unsafeSetFunction ByteString
"json_each"
jsonbEach
:: null 'PGjsonb -|->
("jsonb_each" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson])
jsonbEach :: Expression 'Ungrouped lat with db params '[] (null 'PGjsonb)
-> FromClause
lat
with
db
params
'["jsonb_each"
::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson]]
jsonbEach = ByteString
-> null 'PGjsonb
-|-> ("jsonb_each"
::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson])
forall (fun :: Symbol) (ty :: NullType) (row :: RowType).
KnownSymbol fun =>
ByteString -> ty -|-> (fun ::: row)
unsafeSetFunction ByteString
"jsonb_each"
jsonEachText
:: null 'PGjson -|->
("json_each_text" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext])
jsonEachText :: Expression 'Ungrouped lat with db params '[] (null 'PGjson)
-> FromClause
lat
with
db
params
'["json_each_text"
::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext]]
jsonEachText = ByteString
-> null 'PGjson
-|-> ("json_each_text"
::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext])
forall (fun :: Symbol) (ty :: NullType) (row :: RowType).
KnownSymbol fun =>
ByteString -> ty -|-> (fun ::: row)
unsafeSetFunction ByteString
"json_each_text"
jsonArrayElementsText
:: null 'PGjson -|->
("json_array_elements_text" ::: '["value" ::: 'NotNull 'PGtext])
jsonArrayElementsText :: Expression 'Ungrouped lat with db params '[] (null 'PGjson)
-> FromClause
lat
with
db
params
'["json_array_elements_text" ::: '["value" ::: 'NotNull 'PGtext]]
jsonArrayElementsText = ByteString
-> null 'PGjson
-|-> ("json_array_elements_text"
::: '["value" ::: 'NotNull 'PGtext])
forall (fun :: Symbol) (ty :: NullType) (row :: RowType).
KnownSymbol fun =>
ByteString -> ty -|-> (fun ::: row)
unsafeSetFunction ByteString
"json_array_elements_text"
jsonbEachText
:: null 'PGjsonb -|->
("jsonb_each_text" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext])
jsonbEachText :: Expression 'Ungrouped lat with db params '[] (null 'PGjsonb)
-> FromClause
lat
with
db
params
'["jsonb_each_text"
::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext]]
jsonbEachText = ByteString
-> null 'PGjsonb
-|-> ("jsonb_each_text"
::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext])
forall (fun :: Symbol) (ty :: NullType) (row :: RowType).
KnownSymbol fun =>
ByteString -> ty -|-> (fun ::: row)
unsafeSetFunction ByteString
"jsonb_each_text"
jsonObjectKeys
:: null 'PGjson -|->
("json_object_keys" ::: '["json_object_keys" ::: 'NotNull 'PGtext])
jsonObjectKeys :: Expression 'Ungrouped lat with db params '[] (null 'PGjson)
-> FromClause
lat
with
db
params
'["json_object_keys"
::: '["json_object_keys" ::: 'NotNull 'PGtext]]
jsonObjectKeys = ByteString
-> null 'PGjson
-|-> ("json_object_keys"
::: '["json_object_keys" ::: 'NotNull 'PGtext])
forall (fun :: Symbol) (ty :: NullType) (row :: RowType).
KnownSymbol fun =>
ByteString -> ty -|-> (fun ::: row)
unsafeSetFunction ByteString
"json_object_keys"
jsonbObjectKeys
:: null 'PGjsonb -|->
("jsonb_object_keys" ::: '["jsonb_object_keys" ::: 'NotNull 'PGtext])
jsonbObjectKeys :: Expression 'Ungrouped lat with db params '[] (null 'PGjsonb)
-> FromClause
lat
with
db
params
'["jsonb_object_keys"
::: '["jsonb_object_keys" ::: 'NotNull 'PGtext]]
jsonbObjectKeys = ByteString
-> null 'PGjsonb
-|-> ("jsonb_object_keys"
::: '["jsonb_object_keys" ::: 'NotNull 'PGtext])
forall (fun :: Symbol) (ty :: NullType) (row :: RowType).
KnownSymbol fun =>
ByteString -> ty -|-> (fun ::: row)
unsafeSetFunction ByteString
"jsonb_object_keys"
jsonbArrayElementsText
:: null 'PGjsonb -|->
("jsonb_array_elements_text" ::: '["value" ::: 'NotNull 'PGtext])
jsonbArrayElementsText :: Expression 'Ungrouped lat with db params '[] (null 'PGjsonb)
-> FromClause
lat
with
db
params
'["jsonb_array_elements_text" ::: '["value" ::: 'NotNull 'PGtext]]
jsonbArrayElementsText = ByteString
-> null 'PGjsonb
-|-> ("jsonb_array_elements_text"
::: '["value" ::: 'NotNull 'PGtext])
forall (fun :: Symbol) (ty :: NullType) (row :: RowType).
KnownSymbol fun =>
ByteString -> ty -|-> (fun ::: row)
unsafeSetFunction ByteString
"jsonb_array_elements_text"
type JsonPopulateFunction fun json
= forall db row lat with params
. json `In` PGJsonType
=> TypeExpression db ('NotNull ('PGcomposite row))
-> Expression 'Ungrouped lat with db params '[] ('NotNull json)
-> FromClause lat with db params '[fun ::: row]
unsafePopulateFunction
:: forall fun ty
. KnownSymbol fun => Alias fun -> JsonPopulateFunction fun ty
unsafePopulateFunction :: Alias fun -> JsonPopulateFunction fun ty
unsafePopulateFunction Alias fun
_fun TypeExpression db ('NotNull ('PGcomposite row))
ty Expression 'Ungrouped lat with db params '[] ('NotNull ty)
expr = ByteString -> FromClause lat with db params '[fun ::: row]
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
ByteString -> FromClause lat with db params from
UnsafeFromClause (ByteString -> FromClause lat with db params '[fun ::: row])
-> ByteString -> FromClause lat with db params '[fun ::: row]
forall a b. (a -> b) -> a -> b
$ KnownSymbol fun => ByteString
forall (s :: Symbol). KnownSymbol s => ByteString
renderSymbol @fun
ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized (ByteString
"null::" ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> TypeExpression db ('NotNull ('PGcomposite row)) -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL TypeExpression db ('NotNull ('PGcomposite row))
ty ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString
", " ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> Expression 'Ungrouped lat with db params '[] ('NotNull ty)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression 'Ungrouped lat with db params '[] ('NotNull ty)
expr)
jsonPopulateRecord :: JsonPopulateFunction "json_populate_record" 'PGjson
jsonPopulateRecord :: TypeExpression db ('NotNull ('PGcomposite row))
-> Expression 'Ungrouped lat with db params '[] ('NotNull 'PGjson)
-> FromClause lat with db params '["json_populate_record" ::: row]
jsonPopulateRecord = Alias "json_populate_record"
-> JsonPopulateFunction "json_populate_record" 'PGjson
forall (fun :: Symbol) (ty :: PGType).
KnownSymbol fun =>
Alias fun -> JsonPopulateFunction fun ty
unsafePopulateFunction IsLabel "json_populate_record" (Alias "json_populate_record")
Alias "json_populate_record"
#json_populate_record
jsonbPopulateRecord :: JsonPopulateFunction "jsonb_populate_record" 'PGjsonb
jsonbPopulateRecord :: TypeExpression db ('NotNull ('PGcomposite row))
-> Expression 'Ungrouped lat with db params '[] ('NotNull 'PGjsonb)
-> FromClause lat with db params '["jsonb_populate_record" ::: row]
jsonbPopulateRecord = Alias "jsonb_populate_record"
-> JsonPopulateFunction "jsonb_populate_record" 'PGjsonb
forall (fun :: Symbol) (ty :: PGType).
KnownSymbol fun =>
Alias fun -> JsonPopulateFunction fun ty
unsafePopulateFunction IsLabel "jsonb_populate_record" (Alias "jsonb_populate_record")
Alias "jsonb_populate_record"
#jsonb_populate_record
jsonPopulateRecordSet :: JsonPopulateFunction "json_populate_record_set" 'PGjson
jsonPopulateRecordSet :: TypeExpression db ('NotNull ('PGcomposite row))
-> Expression 'Ungrouped lat with db params '[] ('NotNull 'PGjson)
-> FromClause
lat with db params '["json_populate_record_set" ::: row]
jsonPopulateRecordSet = Alias "json_populate_record_set"
-> JsonPopulateFunction "json_populate_record_set" 'PGjson
forall (fun :: Symbol) (ty :: PGType).
KnownSymbol fun =>
Alias fun -> JsonPopulateFunction fun ty
unsafePopulateFunction IsLabel
"json_populate_record_set" (Alias "json_populate_record_set")
Alias "json_populate_record_set"
#json_populate_record_set
jsonbPopulateRecordSet :: JsonPopulateFunction "jsonb_populate_record_set" 'PGjsonb
jsonbPopulateRecordSet :: TypeExpression db ('NotNull ('PGcomposite row))
-> Expression 'Ungrouped lat with db params '[] ('NotNull 'PGjsonb)
-> FromClause
lat with db params '["jsonb_populate_record_set" ::: row]
jsonbPopulateRecordSet = Alias "jsonb_populate_record_set"
-> JsonPopulateFunction "jsonb_populate_record_set" 'PGjsonb
forall (fun :: Symbol) (ty :: PGType).
KnownSymbol fun =>
Alias fun -> JsonPopulateFunction fun ty
unsafePopulateFunction IsLabel
"jsonb_populate_record_set" (Alias "jsonb_populate_record_set")
Alias "jsonb_populate_record_set"
#jsonb_populate_record_set
type JsonToRecordFunction json
= forall lat with db params tab row
. (SOP.SListI row, json `In` PGJsonType)
=> Expression 'Ungrouped lat with db params '[] ('NotNull json)
-> Aliased (NP (Aliased (TypeExpression db))) (tab ::: row)
-> FromClause lat with db params '[tab ::: row]
unsafeRecordFunction :: ByteString -> JsonToRecordFunction json
unsafeRecordFunction :: ByteString -> JsonToRecordFunction json
unsafeRecordFunction ByteString
fun Expression 'Ungrouped lat with db params '[] ('NotNull json)
expr (NP (Aliased (TypeExpression db)) ty
types `As` Alias alias
tab) = ByteString -> FromClause lat with db params '[tab ::: row]
forall (lat :: FromType) (with :: FromType) (db :: SchemasType)
(params :: [NullType]) (from :: FromType).
ByteString -> FromClause lat with db params from
UnsafeFromClause (ByteString -> FromClause lat with db params '[tab ::: row])
-> ByteString -> FromClause lat with db params '[tab ::: row]
forall a b. (a -> b) -> a -> b
$
ByteString
fun ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized (Expression 'Ungrouped lat with db params '[] ('NotNull json)
-> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Expression 'Ungrouped lat with db params '[] ('NotNull json)
expr) ByteString -> ByteString -> ByteString
<+> ByteString
"AS" ByteString -> ByteString -> ByteString
<+> Alias alias -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias alias
tab
ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> ByteString -> ByteString
parenthesized ((forall (x :: (Symbol, NullType)).
Aliased (TypeExpression db) x -> ByteString)
-> NP (Aliased (TypeExpression db)) ty -> ByteString
forall k (xs :: [k]) (expression :: k -> *).
SListI xs =>
(forall (x :: k). expression x -> ByteString)
-> NP expression xs -> ByteString
renderCommaSeparated forall (db :: SchemasType) (ty :: (Symbol, NullType)).
Aliased (TypeExpression db) ty -> ByteString
forall (x :: (Symbol, NullType)).
Aliased (TypeExpression db) x -> ByteString
renderTy NP (Aliased (TypeExpression db)) ty
types)
where
renderTy :: Aliased (TypeExpression db) ty -> ByteString
renderTy :: Aliased (TypeExpression db) ty -> ByteString
renderTy (TypeExpression db ty
ty `As` Alias alias
alias) = Alias alias -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL Alias alias
alias ByteString -> ByteString -> ByteString
<+> TypeExpression db ty -> ByteString
forall sql. RenderSQL sql => sql -> ByteString
renderSQL TypeExpression db ty
ty
jsonToRecord :: JsonToRecordFunction 'PGjson
jsonToRecord :: Expression 'Ungrouped lat with db params '[] ('NotNull 'PGjson)
-> Aliased (NP (Aliased (TypeExpression db))) (tab ::: row)
-> FromClause lat with db params '[tab ::: row]
jsonToRecord = ByteString -> JsonToRecordFunction 'PGjson
forall (json :: PGType). ByteString -> JsonToRecordFunction json
unsafeRecordFunction ByteString
"json_to_record"
jsonbToRecord :: JsonToRecordFunction 'PGjsonb
jsonbToRecord :: Expression 'Ungrouped lat with db params '[] ('NotNull 'PGjsonb)
-> Aliased (NP (Aliased (TypeExpression db))) (tab ::: row)
-> FromClause lat with db params '[tab ::: row]
jsonbToRecord = ByteString -> JsonToRecordFunction 'PGjsonb
forall (json :: PGType). ByteString -> JsonToRecordFunction json
unsafeRecordFunction ByteString
"jsonb_to_record"
jsonToRecordSet :: JsonToRecordFunction 'PGjson
jsonToRecordSet :: Expression 'Ungrouped lat with db params '[] ('NotNull 'PGjson)
-> Aliased (NP (Aliased (TypeExpression db))) (tab ::: row)
-> FromClause lat with db params '[tab ::: row]
jsonToRecordSet = ByteString -> JsonToRecordFunction 'PGjson
forall (json :: PGType). ByteString -> JsonToRecordFunction json
unsafeRecordFunction ByteString
"json_to_record_set"
jsonbToRecordSet :: JsonToRecordFunction 'PGjsonb
jsonbToRecordSet :: Expression 'Ungrouped lat with db params '[] ('NotNull 'PGjsonb)
-> Aliased (NP (Aliased (TypeExpression db))) (tab ::: row)
-> FromClause lat with db params '[tab ::: row]
jsonbToRecordSet = ByteString -> JsonToRecordFunction 'PGjsonb
forall (json :: PGType). ByteString -> JsonToRecordFunction json
unsafeRecordFunction ByteString
"jsonb_to_record_set"