Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
Json and Jsonb functions and operators
Synopsis
- (.->) :: (json `In` PGJsonType, key `In` PGJsonKey) => Operator (null json) (null key) (Null json)
- (.->>) :: (json `In` PGJsonType, key `In` PGJsonKey) => Operator (null json) (null key) (Null PGtext)
- (.#>) :: json `In` PGJsonType => Operator (null json) (null (PGvararray (NotNull PGtext))) (Null json)
- (.#>>) :: json `In` PGJsonType => Operator (null json) (null (PGvararray (NotNull PGtext))) (Null PGtext)
- (.?) :: Operator (null PGjsonb) (null PGtext) (Null PGbool)
- (.?|) :: Operator (null PGjsonb) (null (PGvararray (NotNull PGtext))) (Null PGbool)
- (.?&) :: Operator (null PGjsonb) (null (PGvararray (NotNull PGtext))) (Null PGbool)
- (.-.) :: key `In` '[PGtext, PGvararray (NotNull PGtext), PGint4, PGint2] => Operator (null PGjsonb) (null key) (null PGjsonb)
- (#-.) :: Operator (null PGjsonb) (null (PGvararray (NotNull PGtext))) (null PGjsonb)
- toJson :: null ty :--> null PGjson
- toJsonb :: null ty :--> null PGjsonb
- arrayToJson :: null (PGvararray ty) :--> null PGjson
- rowToJson :: null (PGcomposite ty) :--> null PGjson
- jsonBuildArray :: SListI tuple => FunctionN tuple (null PGjson)
- jsonbBuildArray :: SListI tuple => FunctionN tuple (null PGjsonb)
- class SListI tys => JsonBuildObject tys where
- jsonBuildObject :: FunctionN tys (null PGjson)
- jsonbBuildObject :: FunctionN tys (null PGjsonb)
- jsonObject :: null (PGfixarray '[n, 2] (NotNull PGtext)) :--> null PGjson
- jsonbObject :: null (PGfixarray '[n, 2] (NotNull PGtext)) :--> null PGjsonb
- jsonZipObject :: FunctionN '[null (PGvararray (NotNull PGtext)), null (PGvararray (NotNull PGtext))] (null PGjson)
- jsonbZipObject :: FunctionN '[null (PGvararray (NotNull PGtext)), null (PGvararray (NotNull PGtext))] (null PGjsonb)
- jsonArrayLength :: null PGjson :--> null PGint4
- jsonbArrayLength :: null PGjsonb :--> null PGint4
- jsonTypeof :: null PGjson :--> null PGtext
- jsonbTypeof :: null PGjsonb :--> null PGtext
- jsonStripNulls :: null PGjson :--> null PGjson
- jsonbStripNulls :: null PGjsonb :--> null PGjsonb
- jsonbSet :: FunctionN '[null PGjsonb, null (PGvararray (NotNull PGtext)), null PGjsonb, null PGbool] (null PGjsonb)
- jsonbInsert :: FunctionN '[null PGjsonb, null (PGvararray (NotNull PGtext)), null PGjsonb, null PGbool] (null PGjsonb)
- jsonbPretty :: null PGjsonb :--> null PGtext
- jsonEach :: SetOfFunction "json_each" (null PGjson) '["key" ::: NotNull PGtext, "value" ::: NotNull PGjson]
- jsonbEach :: SetOfFunction "jsonb_each" (nullity PGjsonb) '["key" ::: NotNull PGtext, "value" ::: NotNull PGjson]
- jsonEachText :: SetOfFunction "json_each_text" (null PGjson) '["key" ::: NotNull PGtext, "value" ::: NotNull PGtext]
- jsonbEachText :: SetOfFunction "jsonb_each_text" (null PGjsonb) '["key" ::: NotNull PGtext, "value" ::: NotNull PGtext]
- jsonObjectKeys :: SetOfFunction "json_object_keys" (nullity PGjson) '["json_object_keys" ::: NotNull PGtext]
- jsonbObjectKeys :: SetOfFunction "jsonb_object_keys" (null PGjsonb) '["jsonb_object_keys" ::: NotNull PGtext]
- type JsonPopulateFunction fun json = forall schemas row outer commons params. json `In` PGJsonType => TypeExpression schemas (NotNull (PGcomposite row)) -> Expression outer commons Ungrouped schemas params '[] (NotNull json) -> FromClause outer commons schemas params '[fun ::: row]
- jsonPopulateRecord :: JsonPopulateFunction "json_populate_record" PGjson
- jsonbPopulateRecord :: JsonPopulateFunction "jsonb_populate_record" PGjsonb
- jsonPopulateRecordSet :: JsonPopulateFunction "json_populate_record_set" PGjson
- jsonbPopulateRecordSet :: JsonPopulateFunction "jsonb_populate_record_set" PGjsonb
- type JsonToRecordFunction json = forall outer commons schemas params tab row. (SListI row, json `In` PGJsonType) => Expression outer commons Ungrouped schemas params '[] (NotNull json) -> Aliased (NP (Aliased (TypeExpression schemas))) (tab ::: row) -> FromClause outer commons schemas params '[tab ::: row]
- jsonToRecord :: JsonToRecordFunction PGjson
- jsonbToRecord :: JsonToRecordFunction PGjsonb
- jsonToRecordSet :: JsonToRecordFunction PGjson
- jsonbToRecordSet :: JsonToRecordFunction PGjsonb
Json and Jsonb operators
(.->) :: (json `In` PGJsonType, key `In` PGJsonKey) => Operator (null json) (null key) (Null json) infixl 8 Source #
Get JSON value (object field or array element) at a key.
(.->>) :: (json `In` PGJsonType, key `In` PGJsonKey) => Operator (null json) (null key) (Null PGtext) infixl 8 Source #
Get JSON value (object field or array element) at a key, as text.
(.#>) :: json `In` PGJsonType => Operator (null json) (null (PGvararray (NotNull PGtext))) (Null json) infixl 8 Source #
Get JSON value at a specified path.
(.#>>) :: json `In` PGJsonType => Operator (null json) (null (PGvararray (NotNull PGtext))) (Null PGtext) infixl 8 Source #
Get JSON value at a specified path as text.
Jsonb operators
(.?) :: Operator (null PGjsonb) (null PGtext) (Null PGbool) infixl 9 Source #
Does the string exist as a top-level key within the JSON value?
(.?|) :: Operator (null PGjsonb) (null (PGvararray (NotNull PGtext))) (Null PGbool) infixl 9 Source #
Do any of these array strings exist as top-level keys?
(.?&) :: Operator (null PGjsonb) (null (PGvararray (NotNull PGtext))) (Null PGbool) infixl 9 Source #
Do all of these array strings exist as top-level keys?
(.-.) :: key `In` '[PGtext, PGvararray (NotNull PGtext), PGint4, PGint2] => Operator (null PGjsonb) (null key) (null PGjsonb) infixl 6 Source #
Delete a key or keys from a JSON object, or remove an array element.
If the right operand is
text
: Delete key / value pair or string element from left operand.
Key / value pairs are matched based on their key value,
text[]
: Delete multiple key / value pairs or string elements
from left operand. Key / value pairs are matched based on their key value,
integer
: Delete the array element with specified index (Negative integers
count from the end). Throws an error if top level container is not an array.
(#-.) :: Operator (null PGjsonb) (null (PGvararray (NotNull PGtext))) (null PGjsonb) infixl 6 Source #
Delete the field or element with specified path (for JSON arrays, negative integers count from the end)
Json and Jsonb functions
toJson :: null ty :--> null PGjson Source #
Returns the value as json. Arrays and composites are converted (recursively) to arrays and objects; otherwise, if there is a cast from the type to json, the cast function will be used to perform the conversion; 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 such a fashion that it is a valid json value.
toJsonb :: null ty :--> null PGjsonb Source #
Returns the value as jsonb. Arrays and composites are converted (recursively) to arrays and objects; otherwise, if there is a cast from the type to json, the cast function will be used to perform the conversion; 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 such a fashion that it is a valid jsonb value.
arrayToJson :: null (PGvararray ty) :--> null PGjson Source #
Returns the array as a JSON array. A PostgreSQL multidimensional array becomes a JSON array of arrays.
jsonBuildArray :: SListI tuple => FunctionN tuple (null PGjson) Source #
Builds a possibly-heterogeneously-typed JSON array out of a variadic argument list.
jsonbBuildArray :: SListI tuple => FunctionN tuple (null PGjsonb) Source #
Builds a possibly-heterogeneously-typed (binary) JSON array out of a variadic argument list.
class SListI tys => JsonBuildObject tys where Source #
Builds a possibly-heterogeneously-typed JSON object out of a variadic argument list. The elements of the argument list must alternate between text and values.
Nothing
jsonBuildObject :: FunctionN tys (null PGjson) Source #
jsonbBuildObject :: FunctionN tys (null PGjsonb) Source #
Instances
JsonBuildObject ([] :: [NullityType]) Source # | |
Defined in Squeal.PostgreSQL.Expression.Json jsonBuildObject :: FunctionN [] (null PGjson) Source # jsonbBuildObject :: FunctionN [] (null PGjsonb) Source # | |
(JsonBuildObject tys, In key PGJsonKey) => JsonBuildObject (NotNull key ': (value ': tys)) Source # | |
Defined in Squeal.PostgreSQL.Expression.Json |
jsonObject :: null (PGfixarray '[n, 2] (NotNull PGtext)) :--> null PGjson Source #
Builds a JSON object out of a text array. The array must have two dimensions such that each inner array has exactly two elements, which are taken as a key/value pair.
jsonbObject :: null (PGfixarray '[n, 2] (NotNull PGtext)) :--> null PGjsonb Source #
Builds a binary JSON object out of a text array. The array must have two dimensions such that each inner array has exactly two elements, which are taken as a key/value pair.
jsonZipObject :: FunctionN '[null (PGvararray (NotNull PGtext)), null (PGvararray (NotNull PGtext))] (null PGjson) Source #
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.
jsonbZipObject :: FunctionN '[null (PGvararray (NotNull PGtext)), null (PGvararray (NotNull PGtext))] (null PGjsonb) Source #
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
object.
jsonArrayLength :: null PGjson :--> null PGint4 Source #
Returns the number of elements in the outermost JSON array.
jsonbArrayLength :: null PGjsonb :--> null PGint4 Source #
Returns the number of elements in the outermost binary JSON array.
jsonTypeof :: null PGjson :--> null PGtext Source #
Returns the type of the outermost JSON value as a text string. Possible types are object, array, string, number, boolean, and null.
jsonbTypeof :: null PGjsonb :--> null PGtext Source #
Returns the type of the outermost binary JSON value as a text string. Possible types are object, array, string, number, boolean, and null.
jsonStripNulls :: null PGjson :--> null PGjson Source #
Returns its argument with all object fields that have null values omitted. Other null values are untouched.
jsonbStripNulls :: null PGjsonb :--> null PGjsonb Source #
Returns its argument with all object fields that have null values omitted. Other null values are untouched.
jsonbSet :: FunctionN '[null PGjsonb, null (PGvararray (NotNull PGtext)), null PGjsonb, null PGbool] (null PGjsonb) Source #
jsonbSet target path new_value create_missing
Returns target with the section designated by path replaced by new_value
,
or with new_value
added if create_missing is
true
and the
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
arrays.
jsonbInsert :: FunctionN '[null PGjsonb, null (PGvararray (NotNull PGtext)), null PGjsonb, null PGbool] (null PGjsonb) Source #
jsonbInsert target path new_value insert_after
Returns target with new_value
inserted. If target section designated by
path is in a JSONB array, new_value
will be inserted before target or after
if insert_after
is true
.
If target section designated by
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
in path count from the end of JSON arrays.
Json and Jsonb set returning functions
jsonEach :: SetOfFunction "json_each" (null PGjson) '["key" ::: NotNull PGtext, "value" ::: NotNull PGjson] Source #
Expands the outermost JSON object into a set of key/value pairs.
>>>
printSQL (select Star (from (jsonEach (literal (Json (object ["a" .= "foo", "b" .= "bar"]))))))
SELECT * FROM json_each(('{"a":"foo","b":"bar"}' :: json))
jsonbEach :: SetOfFunction "jsonb_each" (nullity PGjsonb) '["key" ::: NotNull PGtext, "value" ::: NotNull PGjson] Source #
Expands the outermost binary JSON object into a set of key/value pairs.
>>>
printSQL (select Star (from (jsonbEach (literal (Jsonb (object ["a" .= "foo", "b" .= "bar"]))))))
SELECT * FROM jsonb_each(('{"a":"foo","b":"bar"}' :: jsonb))
jsonEachText :: SetOfFunction "json_each_text" (null PGjson) '["key" ::: NotNull PGtext, "value" ::: NotNull PGtext] Source #
Expands the outermost JSON object into a set of key/value pairs.
>>>
printSQL (select Star (from (jsonEachText (literal (Json (object ["a" .= "foo", "b" .= "bar"]))))))
SELECT * FROM json_each_text(('{"a":"foo","b":"bar"}' :: json))
jsonbEachText :: SetOfFunction "jsonb_each_text" (null PGjsonb) '["key" ::: NotNull PGtext, "value" ::: NotNull PGtext] Source #
Expands the outermost binary JSON object into a set of key/value pairs.
>>>
printSQL (select Star (from (jsonbEachText (literal (Jsonb (object ["a" .= "foo", "b" .= "bar"]))))))
SELECT * FROM jsonb_each_text(('{"a":"foo","b":"bar"}' :: jsonb))
jsonObjectKeys :: SetOfFunction "json_object_keys" (nullity PGjson) '["json_object_keys" ::: NotNull PGtext] Source #
Returns set of keys in the outermost JSON object.
>>>
printSQL (jsonObjectKeys (literal (Json (object ["a" .= "foo", "b" .= "bar"]))))
json_object_keys(('{"a":"foo","b":"bar"}' :: json))
jsonbObjectKeys :: SetOfFunction "jsonb_object_keys" (null PGjsonb) '["jsonb_object_keys" ::: NotNull PGtext] Source #
Returns set of keys in the outermost JSON object.
>>>
printSQL (jsonbObjectKeys (literal (Jsonb (object ["a" .= "foo", "b" .= "bar"]))))
jsonb_object_keys(('{"a":"foo","b":"bar"}' :: jsonb))
type JsonPopulateFunction fun json Source #
= json `In` PGJsonType | |
=> TypeExpression schemas (NotNull (PGcomposite row)) | row type |
-> Expression outer commons Ungrouped schemas params '[] (NotNull json) | json type |
-> FromClause outer commons schemas params '[fun ::: row] |
Build rows from Json types.
jsonPopulateRecord :: JsonPopulateFunction "json_populate_record" PGjson Source #
Expands the JSON expression to a row whose columns match the record type defined by the given table.
jsonbPopulateRecord :: JsonPopulateFunction "jsonb_populate_record" PGjsonb Source #
Expands the binary JSON expression to a row whose columns match the record type defined by the given table.
jsonPopulateRecordSet :: JsonPopulateFunction "json_populate_record_set" PGjson Source #
Expands the outermost array of objects in the given JSON expression to a set of rows whose columns match the record type defined by the given table.
jsonbPopulateRecordSet :: JsonPopulateFunction "jsonb_populate_record_set" PGjsonb Source #
Expands the outermost array of objects in the given binary JSON expression to a set of rows whose columns match the record type defined by the given table.
type JsonToRecordFunction json Source #
= (SListI row, json `In` PGJsonType) | |
=> Expression outer commons Ungrouped schemas params '[] (NotNull json) | json type |
-> Aliased (NP (Aliased (TypeExpression schemas))) (tab ::: row) | row type |
-> FromClause outer commons schemas params '[tab ::: row] |
Build rows from Json types.
jsonToRecord :: JsonToRecordFunction PGjson Source #
Builds an arbitrary record from a JSON object.
jsonbToRecord :: JsonToRecordFunction PGjsonb Source #
Builds an arbitrary record from a binary JSON object.
jsonToRecordSet :: JsonToRecordFunction PGjson Source #
Builds an arbitrary set of records from a JSON array of objects.
jsonbToRecordSet :: JsonToRecordFunction PGjsonb Source #
Builds an arbitrary set of records from a binary JSON array of objects.