查看源代码 json (stdlib v6.2)

一个用于编码和解码 JSON 的库。

此模块实现了 EEP68

编码器和解码器都完全符合 RFC 8259ECMA 404 标准。解码器使用 JSONTestSuite 进行测试。

摘要

函数

Binary 解析 JSON 值。

Binary 解析 JSON 值。

继续解析 JSON 值的字节流。

开始解析 JSON 值的字节流。

生成与 Term 对应的 JSON。

生成与 Term 对应的 JSON。

json:encode/1 使用的原子默认编码器。

json:encode/1 使用的二进制作为 JSON 字符串的默认编码器。

将二进制编码为生成纯 ASCII JSON 的 JSON 字符串的编码器。

json:encode/1 使用的浮点数作为 JSON 数字的默认编码器。

json:encode/1 使用的整数作为 JSON 数字的默认编码器。

用于将键值对列表编码为 JSON 对象的编码器。

用于将键值对列表编码为 JSON 对象的编码器。

json:encode/1 使用的列表作为 JSON 数组的默认编码器。

json:encode/1 使用的映射作为 JSON 对象的默认编码器。

用于将映射编码为 JSON 对象的编码器。

json:encode/1 使用的默认编码器。

生成与 Term 对应的格式化 JSON。

生成与 Term 对应的格式化 JSON。

生成与 Term 对应的格式化 JSON。

用于将键值对列表格式化为 JSON 对象的格式化函数。

用于将键值对列表格式化为 JSON 对象的格式化函数。

json:format/1 使用的默认格式化函数。

类型

链接到此类型

array_finish_fun()

查看源代码 (自 OTP 27.0 起)
-type array_finish_fun() :: fun((ArrayAcc :: dynamic(), OldAcc :: dynamic()) -> {dynamic(), dynamic()}).
链接到此类型

array_push_fun()

查看源代码 (自 OTP 27.0 起)
-type array_push_fun() :: fun((Value :: dynamic(), Acc :: dynamic()) -> NewAcc :: dynamic()).
链接到此类型

array_start_fun()

查看源代码 (自 OTP 27.0 起)
-type array_start_fun() :: fun((Acc :: dynamic()) -> ArrayAcc :: dynamic()).
链接到此不透明类型

continuation_state()

查看源代码 (自 OTP 27.0 起)
-opaque continuation_state()
链接到此类型

decode_value()

查看源代码 (自 OTP 27.0 起)
-type decode_value() ::
          integer() |
          float() |
          boolean() |
          null |
          binary() |
          [decode_value()] |
          #{binary() => decode_value()}.
链接到此类型

decoders()

查看源代码 (自 OTP 27.0 起)
-type decoders() ::
          #{array_start => array_start_fun(),
            array_push => array_push_fun(),
            array_finish => array_finish_fun(),
            object_start => object_start_fun(),
            object_push => object_push_fun(),
            object_finish => object_finish_fun(),
            float => from_binary_fun(),
            integer => from_binary_fun(),
            string => from_binary_fun(),
            null => term()}.
链接到此类型

encode_map(Value)

查看源代码 (未导出) (自 OTP 27.0 起)
-type encode_map(Value) :: #{binary() | atom() | integer() => Value}.
链接到此类型

encode_value()

查看源代码 (自 OTP 27.0 起)
-type encode_value() ::
          integer() |
          float() |
          boolean() |
          null |
          binary() |
          atom() |
          [encode_value()] |
          encode_map(encode_value()).

可以使用 json:encode/1 编码的简单 JSON 值。

链接到此类型

encoder()

查看源代码 (自 OTP 27.0 起)
-type encoder() :: fun((dynamic(), encoder()) -> iodata()).
链接到此类型

formatter()

查看源代码 (自 OTP 27.0 起)
-type formatter() :: fun((Term :: dynamic(), Encoder :: formatter(), State :: map()) -> iodata()).
链接到此类型

from_binary_fun()

查看源代码 (自 OTP 27.0 起)
-type from_binary_fun() :: fun((binary()) -> dynamic()).
链接到此类型

object_finish_fun()

查看源代码 (自 OTP 27.0 起)
-type object_finish_fun() ::
          fun((ObjectAcc :: dynamic(), OldAcc :: dynamic()) -> {dynamic(), dynamic()}).
链接到此类型

object_push_fun()

查看源代码 (自 OTP 27.0 起)
-type object_push_fun() ::
          fun((Key :: dynamic(), Value :: dynamic(), Acc :: dynamic()) -> NewAcc :: dynamic()).
链接到此类型

object_start_fun()

查看源代码 (自 OTP 27.0 起)
-type object_start_fun() :: fun((Acc :: dynamic()) -> ObjectAcc :: dynamic()).

函数

链接到此函数

decode(Binary)

查看源代码 (自 OTP 27.0 起)
-spec decode(binary()) -> decode_value().

Binary 解析 JSON 值。

支持基本数据映射

JSONErlang
数字integer() | float()
布尔值true | false
空值null
字符串binary()
对象#{binary() => _}

错误

  • 如果 Binary 包含不完整的 JSON 值,则返回 error(unexpected_end)
  • 如果 Binary 包含意外字节或无效的 UTF-8 字节,则返回 error({invalid_byte, Byte})
  • 如果 Binary 包含无效的 UTF-8 转义,则返回 error({unexpected_sequence, Bytes})

示例

> json:decode(<<"{\"foo\": 1}">>).
#{<<"foo">> => 1}
链接到此函数

decode(Binary, Acc0, Decoders)

查看源代码 (自 OTP 27.0 起)
-spec decode(binary(), dynamic(), decoders()) -> {Result :: dynamic(), Acc :: dynamic(), binary()}.

Binary 解析 JSON 值。

decode/1 类似,不同之处在于可以使用 Decoders 中指定的回调函数自定义解码过程。回调函数将使用 Acc 值作为初始累加器。

任何剩余的、未解析的 Binary 数据都将被返回。

默认回调

所有回调都是可选的。如果未提供,它们将回退到 decode/1 函数使用的实现

  • 对于 array_start: fun(_) -> [] end
  • 对于 array_push: fun(Elem, Acc) -> [Elem | Acc] end

  • 对于 array_finish: fun(Acc, OldAcc) -> {lists:reverse(Acc), OldAcc} end
  • 对于 object_start: fun(_) -> [] end
  • 对于 object_push: fun(Key, Value, Acc) -> [{Key, Value} | Acc] end

  • 对于 object_finish: fun(Acc, OldAcc) -> {maps:from_list(Acc), OldAcc} end
  • 对于 float: fun erlang:binary_to_float/1
  • 对于 integer: fun erlang:binary_to_integer/1
  • 对于 string: fun (Value) -> Value end
  • 对于 null: 原子 null

错误

  • 如果 Binary 包含意外字节或无效的 UTF-8 字节,则返回 error({invalid_byte, Byte})
  • 如果 Binary 包含无效的 UTF-8 转义,则返回 error({unexpected_sequence, Bytes})
  • 如果 Binary 包含不完整的 JSON 值,则返回 error(unexpected_end)

示例

将对象键解码为原子

> Push = fun(Key, Value, Acc) -> [{binary_to_existing_atom(Key), Value} | Acc] end.
> json:decode(<<"{\"foo\": 1}">>, ok, #{object_push => Push}).
{#{foo => 1},ok,<<>>}
链接到此函数

decode_continue/2

查看源代码 (自 OTP 27.0 起)
-spec decode_continue(binary() | end_of_input, Opaque :: term()) ->
                         {Result :: dynamic(), Acc :: dynamic(), binary()} |
                         {continue, continuation_state()}.

继续解析 JSON 值的字节流。

decode_start/3 类似,如果函数返回 {continue, State} 并且没有更多数据,则使用 end_of_input 而不是二进制。

> {continue, State} = json:decode_start(<<"{\"foo\":">>, ok, #{}).
> json:decode_continue(<<"1}">>, State).
{#{foo => 1},ok,<<>>}
> {continue, State} = json:decode_start(<<"123">>, ok, #{}).
> json:decode_continue(end_of_input, State).
{123,ok,<<>>}
链接到此函数

decode_start(Binary, Acc, Decoders)

查看源代码 (自 OTP 27.0 起)
-spec decode_start(binary(), dynamic(), decoders()) ->
                      {Result :: dynamic(), Acc :: dynamic(), binary()} |
                      {continue, continuation_state()}.

开始解析 JSON 值的字节流。

decode/3 类似,但当可以解析完整的 JSON 值时返回,或者当数据不完整时返回 {continue, State},当有更多数据可用时,可以将 State 馈送到 decode_continue/2 函数。

链接到此函数

encode(Term)

查看源代码 (自 OTP 27.0 起)
-spec encode(encode_value()) -> iodata().

生成与 Term 对应的 JSON。

支持基本数据映射

ErlangJSON
integer() | float()数字
true | false布尔值
null空值
binary()字符串
atom()字符串
list()数组
#{binary() => _}对象
#{atom() => _}对象
#{integer() => _}对象

这等效于 encode(Term, fun json:encode_value/2)

示例

> iolist_to_binary(json:encode(#{foo => <<"bar">>})).
<<"{\"foo\":\"bar\"}">>
链接到此函数

encode(Term, Encoder)

查看源代码 (自 OTP 27.0 起)
-spec encode(dynamic(), encoder()) -> iodata().

生成与 Term 对应的 JSON。

可以使用 Encoder 回调函数进行自定义。将为所有要编码的数据递归调用回调函数,并期望返回相应的编码 JSON 作为 iodata。

此模块中的各种 encode_* 函数可用于帮助构建此类回调。

示例

一个使用启发式方法来区分类似对象的键值对列表和普通列表的编码器

> encoder([{_, _} | _] = Value, Encode) -> json:encode_key_value_list(Value, Encode);
> encoder(Other, Encode) -> json:encode_value(Other, Encode).
> custom_encode(Value) -> json:encode(Value, fun(Value, Encode) -> encoder(Value, Encode) end).
> iolist_to_binary(custom_encode([{a, []}, {b, 1}])).
<<"{\"a\":[],\"b\":1}">>
链接到此函数

encode_atom/2

查看源代码 (自 OTP 27.0 起)
-spec encode_atom(atom(), encoder()) -> iodata().

json:encode/1 使用的原子默认编码器。

将原子 null 编码为 JSON null,将原子 truefalse 编码为 JSON 布尔值,其他所有内容都编码为 JSON 字符串,并使用相应的二进制调用 Encode 回调。

链接到此函数

encode_binary(Bin)

查看源代码 (自 OTP 27.0 起)
-spec encode_binary(binary()) -> iodata().

json:encode/1 使用的二进制作为 JSON 字符串的默认编码器。

错误

  • 如果二进制文件包含不完整的 UTF-8 序列,则返回 error(unexpected_end)
  • 如果二进制文件包含无效的 UTF-8 序列,则返回 error({invalid_byte, Byte})
链接到此函数

encode_binary_escape_all(Bin)

查看源代码 (自 OTP 27.0 起)
-spec encode_binary_escape_all(binary()) -> iodata().

将二进制编码为生成纯 ASCII JSON 的 JSON 字符串的编码器。

对于任何非 ASCII Unicode 字符,都会使用相应的 \\uXXXX 序列。

错误

  • 如果二进制文件包含不完整的 UTF-8 序列,则返回 error(unexpected_end)
  • 如果二进制文件包含无效的 UTF-8 序列,则返回 error({invalid_byte, Byte})
链接到此函数

encode_float(Float)

查看源代码 (自 OTP 27.0 起)
-spec encode_float(float()) -> iodata().

json:encode/1 使用的浮点数作为 JSON 数字的默认编码器。

链接到此函数

encode_integer(Integer)

查看源代码 (自 OTP 27.0 起)
-spec encode_integer(integer()) -> iodata().

json:encode/1 使用的整数作为 JSON 数字的默认编码器。

链接到此函数

encode_key_value_list(List, Encode)

查看源代码 (自 OTP 27.0 起)
-spec encode_key_value_list([{term(), term()}], encoder()) -> iodata().

用于将键值对列表编码为 JSON 对象的编码器。

接受带有原子、二进制、整数或浮点数键的列表。

链接到此函数

encode_key_value_list_checked(List, Encode)

查看源代码 (自 OTP 27.0 起)
-spec encode_key_value_list_checked([{term(), term()}], encoder()) -> iodata().

用于将键值对列表编码为 JSON 对象的编码器。

接受带有原子、二进制、整数或浮点数键的列表。验证在生成的 JSON 对象中不会产生重复的键。

错误

如果存在重复项,则引发 error({duplicate_key, Key})

链接到此函数

encode_list(List, Encode)

查看源代码 (自 OTP 27.0 起)
-spec encode_list(list(), encoder()) -> iodata().

json:encode/1 使用的列表作为 JSON 数组的默认编码器。

链接到此函数

encode_map(Map, Encode)

查看源代码 (自 OTP 27.0 起)
-spec encode_map(encode_map(dynamic()), encoder()) -> iodata().

json:encode/1 使用的映射作为 JSON 对象的默认编码器。

接受带有原子、二进制、整数或浮点数键的映射。

链接到此函数

encode_map_checked(Map, Encode)

查看源代码 (自 OTP 27.0 起)
-spec encode_map_checked(map(), encoder()) -> iodata().

用于将映射编码为 JSON 对象的编码器。

接受带有原子、二进制、整数或浮点数键的映射。验证在生成的 JSON 对象中不会产生重复的键。

错误

如果存在重复项,则引发 error({duplicate_key, Key})

链接到此函数

encode_value(Value, Encode)

查看源代码 (自 OTP 27.0 起)
-spec encode_value(dynamic(), encoder()) -> iodata().

json:encode/1 使用的默认编码器。

递归地在 Value 中的所有值上调用 Encode

链接到此函数

format(Term)

查看源代码 (自 OTP 27.1 起)
-spec format(Term :: encode_value()) -> iodata().

生成与 Term 对应的格式化 JSON。

类似于 encode/1,但添加了空格以进行格式化。

> io:put_chars(json:format(#{foo => <<"bar">>, baz => 52})).
{
  "baz": 52,
  "foo": "bar"
}
ok
链接到此函数

format/2

查看源代码 (自 OTP 27.1 起)
-spec format(Term :: encode_value(), Opts :: map()) -> iodata();
            (Term :: dynamic(), Encoder :: formatter()) -> iodata().

生成与 Term 对应的格式化 JSON。

等效于 format(Term, fun json:format_value/3, Options)format(Term, Encoder, #{})

链接到此函数

format(Term, Encoder, Options)

查看源代码 (自 OTP 27.1 起)
-spec format(Term :: dynamic(), Encoder :: formatter(), Options :: map()) -> iodata().

生成与 Term 对应的格式化 JSON。

类似于 encode/2,可以使用 Encoder 回调和 Options 进行自定义。

Options 可以包括 'indent' 来指定每级的空格数,以及 'max' 来粗略地限制列表的宽度。

Encoder 将获得一个 'State' 参数,该参数包含 'Options' 映射,这些映射在递归遍历 'Term' 时与其他数据合并。

此模块中的 format_value/3 或各种 encode_* 函数可用于帮助构建此类回调。

> formatter({posix_time, SysTimeSecs}, Encode, State) ->
    TimeStr = calendar:system_time_to_rfc3339(SysTimeSecs, [{offset, "Z"}]),
    json:format_value(unicode:characters_to_binary(TimeStr), Encode, State);
> formatter(Other, Encode, State) -> json:format_value(Other, Encode, State).
>
> Fun = fun(Value, Encode, State) -> formatter(Value, Encode, State) end.
> Options = #{indent => 4}.
> Term = #{id => 1, time => {posix_time, erlang:system_time(seconds)}}.
>
> io:put_chars(json:format(Term, Fun, Options)).
{
    "id": 1,
    "time": "2024-05-23T16:07:48Z"
}
ok
链接到此函数

format_key_value_list/3

查看源代码 (自 OTP 27.2 起)
-spec format_key_value_list([{term(), term()}], Encode :: formatter(), State :: map()) -> iodata().

用于将键值对列表格式化为 JSON 对象的格式化函数。

接受带有原子、二进制、整数或浮点数键的列表。

链接到此函数

format_key_value_list_checked(KVList, UserEnc, State)

查看源代码 (自 OTP 27.2 起)
-spec format_key_value_list_checked([{term(), term()}], Encoder :: formatter(), State :: map()) ->
                                       iodata().

用于将键值对列表格式化为 JSON 对象的格式化函数。

接受带有原子、二进制、整数或浮点数键的列表。验证在生成的 JSON 对象中不会产生重复的键。

错误

如果存在重复项,则引发 error({duplicate_key, Key})

链接到此函数

format_value(Value, Encode, State)

查看源代码 (自 OTP 27.1 起)
-spec format_value(Value :: dynamic(), Encode :: formatter(), State :: map()) -> iodata().

json:format/1 使用的默认格式化函数。

递归地在 Value 中的所有值上调用 Encode,并缩进对象和列表。