{-# 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
, jsonbEachText
, 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 .->
(.->) = unsafeBinaryOp "->"
(.->>)
:: (json `In` PGJsonType, key `In` PGJsonKey)
=> Operator (null json) (null key) ('Null 'PGtext)
infixl 8 .->>
(.->>) = unsafeBinaryOp "->>"
(.#>)
:: json `In` PGJsonType
=> Operator (null json) (null ('PGvararray ('NotNull 'PGtext))) ('Null json)
infixl 8 .#>
(.#>) = unsafeBinaryOp "#>"
(.#>>)
:: json `In` PGJsonType
=> Operator (null json) (null ('PGvararray ('NotNull 'PGtext))) ('Null 'PGtext)
infixl 8 .#>>
(.#>>) = unsafeBinaryOp "#>>"
(.?) :: Operator (null 'PGjsonb) (null 'PGtext) ('Null 'PGbool)
infixl 9 .?
(.?) = unsafeBinaryOp "?"
(.?|) :: Operator
(null 'PGjsonb)
(null ('PGvararray ('NotNull 'PGtext)))
('Null 'PGbool)
infixl 9 .?|
(.?|) = unsafeBinaryOp "?|"
(.?&) :: Operator
(null 'PGjsonb)
(null ('PGvararray ('NotNull 'PGtext)))
('Null 'PGbool)
infixl 9 .?&
(.?&) = unsafeBinaryOp "?&"
(.-.)
:: key `In` '[ 'PGtext, 'PGvararray ('NotNull 'PGtext), 'PGint4, 'PGint2 ]
=> Operator (null 'PGjsonb) (null key) (null 'PGjsonb)
infixl 6 .-.
(.-.) = unsafeBinaryOp "-"
(#-.) :: Operator (null 'PGjsonb) (null ('PGvararray ('NotNull 'PGtext))) (null 'PGjsonb)
infixl 6 #-.
(#-.) = unsafeBinaryOp "#-"
toJson :: null ty --> null 'PGjson
toJson = unsafeFunction "to_json"
toJsonb :: null ty --> null 'PGjsonb
toJsonb = unsafeFunction "to_jsonb"
arrayToJson :: null ('PGvararray ty) --> null 'PGjson
arrayToJson = unsafeFunction "array_to_json"
rowToJson :: null ('PGcomposite ty) --> null 'PGjson
rowToJson = unsafeFunction "row_to_json"
jsonBuildArray :: SOP.SListI tuple => tuple ---> null 'PGjson
jsonBuildArray = unsafeFunctionN "json_build_array"
jsonbBuildArray :: SOP.SListI tuple => tuple ---> null 'PGjsonb
jsonbBuildArray = unsafeFunctionN "jsonb_build_array"
class SOP.SListI tys => JsonBuildObject tys where
jsonBuildObject :: tys ---> null 'PGjson
jsonBuildObject = unsafeFunctionN "json_build_object"
jsonbBuildObject :: tys ---> null 'PGjsonb
jsonbBuildObject = unsafeFunctionN "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 = unsafeFunction "json_object"
jsonbObject
:: null ('PGfixarray '[n,2] ('NotNull 'PGtext))
--> null 'PGjsonb
jsonbObject = unsafeFunction "jsonb_object"
jsonZipObject ::
'[ null ('PGvararray ('NotNull 'PGtext))
, null ('PGvararray ('NotNull 'PGtext)) ]
---> null 'PGjson
jsonZipObject = unsafeFunctionN "json_object"
jsonbZipObject ::
'[ null ('PGvararray ('NotNull 'PGtext))
, null ('PGvararray ('NotNull 'PGtext)) ]
---> null 'PGjsonb
jsonbZipObject = unsafeFunctionN "jsonb_object"
jsonArrayLength :: null 'PGjson --> null 'PGint4
jsonArrayLength = unsafeFunction "json_array_length"
jsonbArrayLength :: null 'PGjsonb --> null 'PGint4
jsonbArrayLength = unsafeFunction "jsonb_array_length"
jsonTypeof :: null 'PGjson --> null 'PGtext
jsonTypeof = unsafeFunction "json_typeof"
jsonbTypeof :: null 'PGjsonb --> null 'PGtext
jsonbTypeof = unsafeFunction "jsonb_typeof"
jsonStripNulls :: null 'PGjson --> null 'PGjson
jsonStripNulls = unsafeFunction "json_strip_nulls"
jsonbStripNulls :: null 'PGjsonb --> null 'PGjsonb
jsonbStripNulls = unsafeFunction "jsonb_strip_nulls"
jsonbSet ::
'[ null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext))
, null 'PGjsonb, null 'PGbool ] ---> null 'PGjsonb
jsonbSet = unsafeFunctionN "jsonbSet"
jsonbInsert ::
'[ null 'PGjsonb, null ('PGvararray ('NotNull 'PGtext))
, null 'PGjsonb, null 'PGbool ] ---> null 'PGjsonb
jsonbInsert = unsafeFunctionN "jsonb_insert"
jsonbPretty :: null 'PGjsonb --> null 'PGtext
jsonbPretty = unsafeFunction "jsonb_pretty"
jsonEach :: null 'PGjson -|->
("json_each" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson])
jsonEach = unsafeSetFunction "json_each"
jsonbEach
:: null 'PGjsonb -|->
("jsonb_each" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson])
jsonbEach = unsafeSetFunction "jsonb_each"
jsonEachText
:: null 'PGjson -|->
("json_each_text" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext])
jsonEachText = unsafeSetFunction "json_each_text"
jsonbEachText
:: null 'PGjsonb -|->
("jsonb_each_text" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext])
jsonbEachText = unsafeSetFunction "jsonb_each_text"
jsonObjectKeys
:: null 'PGjson -|->
("json_object_keys" ::: '["json_object_keys" ::: 'NotNull 'PGtext])
jsonObjectKeys = unsafeSetFunction "json_object_keys"
jsonbObjectKeys
:: null 'PGjsonb -|->
("jsonb_object_keys" ::: '["jsonb_object_keys" ::: 'NotNull 'PGtext])
jsonbObjectKeys = unsafeSetFunction "jsonb_object_keys"
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 _fun ty expr = UnsafeFromClause $ renderSymbol @fun
<> parenthesized ("null::" <> renderSQL ty <> ", " <> renderSQL expr)
jsonPopulateRecord :: JsonPopulateFunction "json_populate_record" 'PGjson
jsonPopulateRecord = unsafePopulateFunction #json_populate_record
jsonbPopulateRecord :: JsonPopulateFunction "jsonb_populate_record" 'PGjsonb
jsonbPopulateRecord = unsafePopulateFunction #jsonb_populate_record
jsonPopulateRecordSet :: JsonPopulateFunction "json_populate_record_set" 'PGjson
jsonPopulateRecordSet = unsafePopulateFunction #json_populate_record_set
jsonbPopulateRecordSet :: JsonPopulateFunction "jsonb_populate_record_set" 'PGjsonb
jsonbPopulateRecordSet = unsafePopulateFunction #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 fun expr (types `As` tab) = UnsafeFromClause $
fun <> parenthesized (renderSQL expr) <+> "AS" <+> renderSQL tab
<> parenthesized (renderCommaSeparated renderTy types)
where
renderTy :: Aliased (TypeExpression db) ty -> ByteString
renderTy (ty `As` alias) = renderSQL alias <+> renderSQL ty
jsonToRecord :: JsonToRecordFunction 'PGjson
jsonToRecord = unsafeRecordFunction "json_to_record"
jsonbToRecord :: JsonToRecordFunction 'PGjsonb
jsonbToRecord = unsafeRecordFunction "jsonb_to_record"
jsonToRecordSet :: JsonToRecordFunction 'PGjson
jsonToRecordSet = unsafeRecordFunction "json_to_record_set"
jsonbToRecordSet :: JsonToRecordFunction 'PGjsonb
jsonbToRecordSet = unsafeRecordFunction "jsonb_to_record_set"