squeal-postgresql-0.9.1.3: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Squeal.PostgreSQL.Expression.Json

Description

json and jsonb functions and operators

Synopsis

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.

rowToJson :: null ('PGcomposite ty) --> null 'PGjson Source #

Returns the row as a JSON object.

jsonBuildArray :: SListI tuple => tuple ---> null 'PGjson Source #

Builds a possibly-heterogeneously-typed JSON array out of a variadic argument list.

jsonbBuildArray :: SListI tuple => 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.

Minimal complete definition

Nothing

Instances

Instances details
JsonBuildObject ('[] :: [NullType]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Json

Methods

jsonBuildObject :: forall (null :: PGType -> NullType). '[] ---> null 'PGjson Source #

jsonbBuildObject :: forall (null :: PGType -> NullType). '[] ---> null 'PGjsonb Source #

(JsonBuildObject tys, In key PGJsonKey) => JsonBuildObject ('NotNull key ': (value ': tys)) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Json

Methods

jsonBuildObject :: forall (null :: PGType -> NullType). ('NotNull key ': (value ': tys)) ---> null 'PGjson Source #

jsonbBuildObject :: forall (null :: PGType -> NullType). ('NotNull key ': (value ': tys)) ---> null 'PGjsonb Source #

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 :: '[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 :: '[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 :: '[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 :: '[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.

jsonbPretty :: null 'PGjsonb --> null 'PGtext Source #

Returns its argument as indented JSON text.

Json and Jsonb Set Functions

jsonEach :: null 'PGjson -|-> ("json_each" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGjson]) Source #

Expands the outermost JSON object into a set of key/value pairs.

>>> printSQL (select Star (from (jsonEach (inline (Json (object ["a" .= "foo"]))))))
SELECT * FROM json_each(('{"a":"foo"}' :: json))

jsonbEach :: null 'PGjsonb -|-> ("jsonb_each" ::: '["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 (inline (Jsonb (object ["a" .= "foo"]))))))
SELECT * FROM jsonb_each(('{"a":"foo"}' :: jsonb))

jsonEachText :: null 'PGjson -|-> ("json_each_text" ::: '["key" ::: 'NotNull 'PGtext, "value" ::: 'NotNull 'PGtext]) Source #

Expands the outermost JSON object into a set of key/value pairs.

>>> printSQL (select Star (from (jsonEachText (inline (Json (object ["a" .= "foo"]))))))
SELECT * FROM json_each_text(('{"a":"foo"}' :: json))

jsonArrayElementsText :: null 'PGjson -|-> ("json_array_elements_text" ::: '["value" ::: 'NotNull 'PGtext]) Source #

Returns a set of text values from a JSON array

>>> printSQL (select Star (from (jsonArrayElementsText (inline (Json (toJSON ["monkey", "pony", "bear"] ))))))
SELECT * FROM json_array_elements_text(('["monkey","pony","bear"]' :: json))

jsonbEachText :: null 'PGjsonb -|-> ("jsonb_each_text" ::: '["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 (inline (Jsonb (object ["a" .= "foo"]))))))
SELECT * FROM jsonb_each_text(('{"a":"foo"}' :: jsonb))

jsonbArrayElementsText :: null 'PGjsonb -|-> ("jsonb_array_elements_text" ::: '["value" ::: 'NotNull 'PGtext]) Source #

Returns a set of text values from a binary JSON array

>>> printSQL (select Star (from (jsonbArrayElementsText (inline (Jsonb (toJSON ["red", "green", "cyan"] ))))))
SELECT * FROM jsonb_array_elements_text(('["red","green","cyan"]' :: jsonb))

jsonObjectKeys :: null 'PGjson -|-> ("json_object_keys" ::: '["json_object_keys" ::: 'NotNull 'PGtext]) Source #

Returns set of keys in the outermost JSON object.

>>> printSQL (jsonObjectKeys (inline (Json (object ["a" .= "foo"]))))
json_object_keys(('{"a":"foo"}' :: json))

jsonbObjectKeys :: null 'PGjsonb -|-> ("jsonb_object_keys" ::: '["jsonb_object_keys" ::: 'NotNull 'PGtext]) Source #

Returns set of keys in the outermost JSON object.

>>> printSQL (jsonbObjectKeys (inline (Jsonb (object ["a" .= "foo"]))))
jsonb_object_keys(('{"a":"foo"}' :: jsonb))

type JsonPopulateFunction fun json Source #

Arguments

 = forall db row lat with params. json `In` PGJsonType 
=> TypeExpression db ('NotNull ('PGcomposite row))

row type

-> Expression 'Ungrouped lat with db params '[] ('NotNull json)

json type

-> FromClause lat with db 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 #

Arguments

 = forall lat with db params tab row. (SListI row, json `In` PGJsonType) 
=> Expression 'Ungrouped lat with db params '[] ('NotNull json)

json type

-> Aliased (NP (Aliased (TypeExpression db))) (tab ::: row)

row type

-> FromClause lat with db 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.