Skip to content

Commit

Permalink
Fix since tags (json)
Browse files Browse the repository at this point in the history
And also add the copyright to the OTP copyright file.
  • Loading branch information
dgud committed Mar 8, 2024
1 parent 30cc826 commit 5af3dac
Show file tree
Hide file tree
Showing 2 changed files with 47 additions and 0 deletions.
18 changes: 18 additions & 0 deletions lib/stdlib/src/json.erl
Original file line number Diff line number Diff line change
Expand Up @@ -132,6 +132,7 @@ This is equivalent to `encode(Term, fun json:encode_value/2)`.
<<"{\"foo\":\"bar\"}">>
```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode(encode_value()) -> iodata().
encode(Term) -> encode(Term, fun do_encode/2).
Expand Down Expand Up @@ -159,6 +160,7 @@ lists of key-value pairs from plain lists:
<<"{\"a\":[],\"b\":1}">>
```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode(dynamic(), encoder()) -> iodata().
encode(Term, Encoder) when is_function(Encoder, 2) ->
Encoder(Term, Encoder).
Expand All @@ -169,6 +171,7 @@ Default encoder used by `json:encode/1`.
Recursively calls `Encode` on all the values in `Value`.
""".
-spec encode_value(dynamic(), encoder()) -> iodata().
-doc(#{since => <<"OTP 27.0">>}).
encode_value(Value, Encode) ->
do_encode(Value, Encode).
Expand Down Expand Up @@ -197,6 +200,7 @@ and everything else as JSON strings calling the `Encode`
callback with the corresponding binary.
""".
-spec encode_atom(atom(), encoder()) -> iodata().
-doc(#{since => <<"OTP 27.0">>}).
encode_atom(null, _Encode) -> <<"null">>;
encode_atom(true, _Encode) -> <<"true">>;
encode_atom(false, _Encode) -> <<"false">>;
Expand All @@ -205,18 +209,21 @@ encode_atom(Other, Encode) -> Encode(atom_to_binary(Other, utf8), Encode).
-doc """
Default encoder for integers as JSON numbers used by `json:encode/1`.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_integer(integer()) -> iodata().
encode_integer(Integer) -> integer_to_binary(Integer).
-doc """
Default encoder for floats as JSON numbers used by `json:encode/1`.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_float(float()) -> iodata().
encode_float(Float) -> float_to_binary(Float, [short]).
-doc """
Default encoder for lists as JSON arrays used by `json:encode/1`.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_list(list(), encoder()) -> iodata().
encode_list(List, Encode) when is_list(List) ->
do_encode_list(List, Encode).
Expand All @@ -234,6 +241,7 @@ Default encoder for maps as JSON objects used by `json:encode/1`.

Accepts maps with atom, binary, integer, or float keys.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_map(encode_map(dynamic()), encoder()) -> iodata().
encode_map(Map, Encode) when is_map(Map) ->
do_encode_map(Map, Encode).
Expand All @@ -252,6 +260,7 @@ resulting JSON object.

Raises `error({duplicate_key, Key})` if there are duplicates.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_map_checked(map(), encoder()) -> iodata().
encode_map_checked(Map, Encode) ->
do_encode_checked(maps:to_list(Map), Encode).
Expand All @@ -261,6 +270,7 @@ Encoder for lists of key-value pairs as JSON objects.

Accepts lists with atom, binary, integer, or float keys.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_key_value_list([{term(), term()}], encoder()) -> iodata().
encode_key_value_list(List, Encode) when is_function(Encode, 2) ->
encode_object([[$,, key(Key, Encode), $: | Encode(Value, Encode)] || {Key, Value} <- List]).
Expand All @@ -276,6 +286,7 @@ resulting JSON object.

Raises `error({duplicate_key, Key})` if there are duplicates.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_key_value_list_checked([{term(), term()}], encoder()) -> iodata().
encode_key_value_list_checked(List, Encode) ->
do_encode_checked(List, Encode).
Expand Down Expand Up @@ -315,6 +326,7 @@ Default encoder for binaries as JSON strings used by `json:encode/1`.
* `error(unexpected_end)` if the binary contains incomplete UTF-8 sequences.
* `error({invalid_byte, Byte})` if the binary contains invalid UTF-8 sequences.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_binary(binary()) -> iodata().
encode_binary(Bin) when is_binary(Bin) ->
escape_binary(Bin).
Expand All @@ -329,6 +341,7 @@ For any non-ASCII unicode character, a corresponding `\\uXXXX` sequence is used.
* `error(unexpected_end)` if the binary contains incomplete UTF-8 sequences.
* `error({invalid_byte, Byte})` if the binary contains invalid UTF-8 sequences.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec encode_binary_escape_all(binary()) -> iodata().
encode_binary_escape_all(Bin) when is_binary(Bin) ->
escape_all(Bin).
Expand Down Expand Up @@ -601,7 +614,9 @@ Supports basic data mapping:
```erlang
> json:decode(<<"{\"foo\": 1}">>).
#{<<"foo">> => 1}
```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec decode(binary()) -> decode_value().
decode(Binary) when is_binary(Binary) ->
case value(Binary, Binary, 0, ok, [], #decode{}) of
Expand Down Expand Up @@ -659,6 +674,7 @@ Decoding object keys as atoms:
{#{foo => 1},ok,<<>>}
```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec decode(binary(), dynamic(), decoders()) ->
{Result :: dynamic(), Acc :: dynamic(), binary()}.
decode(Binary, Acc0, Decoders) when is_binary(Binary) ->
Expand All @@ -681,6 +697,7 @@ Similar to `decode/3` but returns when a complete JSON value can be parsed or
returns `{continue, State}` for incomplete data,
the `State` can be fed to the `decode_continue/2` function when more data is available.
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec decode_start(binary(), dynamic(), decoders()) ->
{Result :: dynamic(), Acc :: dynamic(), binary()} | {continue, continuation_state()}.
decode_start(Binary, Acc, Decoders) when is_binary(Binary) ->
Expand All @@ -704,6 +721,7 @@ there is no more data, use `end_of_input` instead of a binary.
{123,ok,<<>>}
```
""".
-doc(#{since => <<"OTP 27.0">>}).
-spec decode_continue(binary() | end_of_input, Opaque::term()) ->
{Result :: dynamic(), Acc :: dynamic(), binary()} | {continue, continuation_state()}.
decode_continue(end_of_input, State) ->
Expand Down
29 changes: 29 additions & 0 deletions system/COPYRIGHT
Original file line number Diff line number Diff line change
Expand Up @@ -667,6 +667,35 @@ LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.

---------------------------------------------------------------------------
[json tests]

* Info:
* SPDX-License-Identifier: MIT
* Git Repository: https:/nst/JSONTestSuite
* Commit: 984defc2deaa653cb73cd29f4144a720ec9efe7c
* OTP Location: ./lib/stdlib/test/json_SUITE_data

Copyright (c) 2016 Nicolas Seriot

Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:

The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.

THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.

---------------------------------------------------------------------------
[wx documentation]

Expand Down

0 comments on commit 5af3dac

Please sign in to comment.