Skip to content

Commit

Permalink
More formatting
Browse files Browse the repository at this point in the history
  • Loading branch information
michalmuskala committed Feb 20, 2024
1 parent 4c8e3ca commit adcbed2
Showing 1 changed file with 110 additions and 133 deletions.
243 changes: 110 additions & 133 deletions eeps/eep-0068.md
Original file line number Diff line number Diff line change
Expand Up @@ -121,60 +121,54 @@ For the proposed `json` library this EEP suggests a hybrid approach.

First, a simple, value-based API:

```erlang
-type value() ::
integer() |
float() |
boolean() |
null |
binary() |
list(value()) |
#{binary() => value()}.

-spec decode(binary()) -> value().
```
-type value() ::
integer() |
float() |
boolean() |
null |
binary() |
list(value()) |
#{binary() => value()}.

-spec decode(binary()) -> value().

Error handling is achieved through exceptions. The following errors
are possible:

```erlang
-type error() ::
unexpected_end |
{unexpected_sequence, binary()} |
{invalid_byte, byte()}
```
-type error() ::
unexpected_end |
{unexpected_sequence, binary()} |
{invalid_byte, byte()}

The exceptions might be enhanced through the [Error Info][ERRINFO] mechanism
with additional meta-data like byte offset where the error occured.

For the advanced and customizable API, this EEP proposes a callback-based
API that the decoder will use to produce values from the data it parses.

```erlang
-type from_binary_fun() :: fun((binary()) -> dynamic()).
-type array_start_fun() :: fun((Acc :: dynamic()) -> ArrayAcc :: dynamic()).
-type array_push_fun() :: fun((Value :: dynamic(), Acc :: dynamic()) -> NewAcc :: dynamic()).
-type array_finish_fun() :: fun((ArrayAcc :: dynamic(), OldAcc :: dynamic()) -> {dynamic(), Acc :: dynamic()}).
-type object_start_fun() :: fun((Acc :: dynamic()) -> ObjectAcc :: dynamic()).
-type object_push_fun() :: fun((Key :: dynamic(), Value :: dynamic(), Acc :: dynamic()) -> NewAcc :: dynamic()).
-type object_finish_fun() :: fun((ObjectAcc :: dynamic(), OldAcc :: dynamic()) -> {dynamic(), Acc :: dynamic()}).

-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()
}.

-spec decode(binary(), Acc :: dynamic(), decoders()) ->
{Value :: dynamic(), FinalAcc :: dynamic(), Rest :: binary()}.
```
-type from_binary_fun() :: fun((binary()) -> dynamic()).
-type array_start_fun() :: fun((Acc :: dynamic()) -> ArrayAcc :: dynamic()).
-type array_push_fun() :: fun((Value :: dynamic(), Acc :: dynamic()) -> NewAcc :: dynamic()).
-type array_finish_fun() :: fun((ArrayAcc :: dynamic(), OldAcc :: dynamic()) -> {dynamic(), Acc :: dynamic()}).
-type object_start_fun() :: fun((Acc :: dynamic()) -> ObjectAcc :: dynamic()).
-type object_push_fun() :: fun((Key :: dynamic(), Value :: dynamic(), Acc :: dynamic()) -> NewAcc :: dynamic()).
-type object_finish_fun() :: fun((ObjectAcc :: dynamic(), OldAcc :: dynamic()) -> {dynamic(), Acc :: dynamic()}).

-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()
}.

-spec decode(binary(), Acc :: dynamic(), decoders()) ->
{Value :: dynamic(), FinalAcc :: dynamic(), Rest :: binary()}.

This allows the user to fully customize the decoded format, including
features seen in open-source JSON libraries:
Expand Down Expand Up @@ -219,53 +213,47 @@ it can return an `{incomplete, continuation()}` value that can be used to
decode values split across multiple binary blobs (for example as received
from a TCP socket).

```erlang
-spec decode_continue(binary(), continuation()) ->
{Value :: dynamic(), FinalAcc :: dynamic(), Rest :: binary()} |
{incomplete, continuation()}.
```
-spec decode_continue(binary(), continuation()) ->
{Value :: dynamic(), FinalAcc :: dynamic(), Rest :: binary()} |
{incomplete, continuation()}.

Encoding API
------------

For encoding this EEP again proposes two separate sets of APIs.
A simple API using "canonical" data types:

```erlang
-type encode_value() ::
integer() |
float() |
boolean() |
null |
binary() |
atom() |
list(encode_value()) |
#{binary() | atom() | integer() => encode_value()}.
-type encode_value() ::
integer() |
float() |
boolean() |
null |
binary() |
atom() |
list(encode_value()) |
#{binary() | atom() | integer() => encode_value()}.

-spec encode(encode_value()) -> iodata().
```
-spec encode(encode_value()) -> iodata().

And an advanced, callback-based API allowing for single-pass encoding
of custom data structures. This API is accompanied by a set of functions
facilitating the implementation of custom encoding callbacks.

```erlang
-type encoder() :: fun((dynamic(), encoder()) -> iodata()).
-type encoder() :: fun((dynamic(), encoder()) -> iodata()).

-spec encode(dynamic(), encoder()) -> iodata().
-spec encode(dynamic(), encoder()) -> iodata().

-spec encode_value(dynamic(), encoder()) -> iodata().
-spec encode_atom(atom(), encoder()) -> iodata().
-spec encode_integer(integer()) -> iodata().
-spec encode_float(float()) -> iodata().
-spec encode_list(list(), encoder()) -> iodata().
-spec encode_map(map(), encoder()) -> iodata().
-spec encode_map_checked(map(), encoder()) -> iodata().
-spec encode_key_value_list([{dynamic(), dynamic()}], encoder()) -> iodata().
-spec encode_key_value_list_checked([{dynamic(), dynamic()}], encoder()) -> iodata().
-spec encode_binary(binary()) -> iodata().
-spec encode_binary_escape_all(binary()) -> iodata().
```
-spec encode_value(dynamic(), encoder()) -> iodata().
-spec encode_atom(atom(), encoder()) -> iodata().
-spec encode_integer(integer()) -> iodata().
-spec encode_float(float()) -> iodata().
-spec encode_list(list(), encoder()) -> iodata().
-spec encode_map(map(), encoder()) -> iodata().
-spec encode_map_checked(map(), encoder()) -> iodata().
-spec encode_key_value_list([{dynamic(), dynamic()}], encoder()) -> iodata().
-spec encode_key_value_list_checked([{dynamic(), dynamic()}], encoder()) -> iodata().
-spec encode_binary(binary()) -> iodata().
-spec encode_binary_escape_all(binary()) -> iodata().

The `encoder()` callback is invoked on every value during traversal.
The simple API specified above is equivalent to using the
Expand All @@ -279,7 +267,6 @@ we provide the optional `encode_binary_escape_all/1` function
that will always produce purely ASCII messages encoding all higher
unicode values with the `\u` escape sequences.


Formatting and pretty-printing
------------------------------

Expand All @@ -293,15 +280,13 @@ encoders.
Formatting isn't usually done in critical hot-paths of high-performance
services, therefore the overhead of a two-pass formatting is deemed acceptable.

```erlang
-type format_option() :: #{
indent => iodata(),
line_separator => iodata(),
after_colon => iodata()
}.
-spec format(iodata()) -> iodata().
-spec format(iodata(), format_option()) -> iodata().
```
-type format_option() :: #{
indent => iodata(),
line_separator => iodata(),
after_colon => iodata()
}.
-spec format(iodata()) -> iodata().
-spec format(iodata(), format_option()) -> iodata().

Reference Implementation
========================
Expand All @@ -319,46 +304,42 @@ Example of a decoding trace

Given the following data:

```json
{"a": [[], {}, true, false, null, {"foo": "baz"}], "b": [1, 2.0, "three"]}
```
{"a": [[], {}, true, false, null, {"foo": "baz"}], "b": [1, 2.0, "three"]}

the decoding APIs will be called with the following arguments:

```erlang
object_start(Acc0) => Acc1
string(<<"a">>) => Str1
array_start(Acc1) => Acc2
empty_array() => Arr1
array_push(Acc2, Arr1) => Acc3
empty_object() => Obj1
array_push(Obj1, Acc3) => Acc4
array_push(true, Acc4) => Acc5
array_push(false, Acc5) => Acc6
null() => Null
array_push(Null, Acc6) => Acc7
object_start(Acc7) => Acc8
string(<<"foo">>) => Str2
string(<<"baz">>) => Str3
object_push(Str2, Str3, Acc8) => Acc9
object_finish(Acc9) => Obj2
array_push(Obj2, Acc7) => Acc10
array_finish(Acc10, Acc1) => {Arr1, Acc11}
object_push(Arr1, Acc11) => Acc12
string(<<"b">>) => Str4
array_start(Acc12) => Acc13
integer(<<"1">>) => Int1
array_push(Int1, Acc13) => Acc14
float(<<"2.0">>) => Float1
array_push(Float1, Acc14) => Acc15
string(<<"three">>) => Str5
array_push(Str5, Acc15) => Acc16
array_finish(Acc16, Acc12) => {Arr2, Acc17}
object_push(Str4, Arr2, Acc17) => Acc18
object_finish(Acc18, Acc0) => {Obj3, Acc19}
% final decode/3 return
{Obj3, Acc19, <<"">>}
```
object_start(Acc0) => Acc1
string(<<"a">>) => Str1
array_start(Acc1) => Acc2
empty_array() => Arr1
array_push(Acc2, Arr1) => Acc3
empty_object() => Obj1
array_push(Obj1, Acc3) => Acc4
array_push(true, Acc4) => Acc5
array_push(false, Acc5) => Acc6
null() => Null
array_push(Null, Acc6) => Acc7
object_start(Acc7) => Acc8
string(<<"foo">>) => Str2
string(<<"baz">>) => Str3
object_push(Str2, Str3, Acc8) => Acc9
object_finish(Acc9) => Obj2
array_push(Obj2, Acc7) => Acc10
array_finish(Acc10, Acc1) => {Arr1, Acc11}
object_push(Arr1, Acc11) => Acc12
string(<<"b">>) => Str4
array_start(Acc12) => Acc13
integer(<<"1">>) => Int1
array_push(Int1, Acc13) => Acc14
float(<<"2.0">>) => Float1
array_push(Float1, Acc14) => Acc15
string(<<"three">>) => Str5
array_push(Str5, Acc15) => Acc16
array_finish(Acc16, Acc12) => {Arr2, Acc17}
object_push(Str4, Arr2, Acc17) => Acc18
object_finish(Acc18, Acc0) => {Obj3, Acc19}
% final decode/3 return
{Obj3, Acc19, <<"">>}

Example of a custom encoder
---------------------------
Expand All @@ -367,22 +348,18 @@ An example of a custom encoder that would support using a heuristic
to differentiate pairs of object-like key-value lists from plain
lists of values could look as follows:

```erlang
custom_encode(Value) -> json:encode(Value, fun encoder/2).
custom_encode(Value) -> json:encode(Value, fun encoder/2).

encoder([{_, _} | _] = Value, Encode) -> json:encode_key_value_list(Value, Encode);
encoder(Other, Encode) -> json:encode_value(Other, Encode).
```
encoder([{_, _} | _] = Value, Encode) -> json:encode_key_value_list(Value, Encode);
encoder(Other, Encode) -> json:encode_value(Other, Encode).

Another encoder that supports using Elixir `nil` as Null and protocols for
further customisation could look as follows:

```erlang
encoder(nil, _Encode) -> <<"null">>;
encoder(null, _Encode) -> <<"\"null\"">>;
encoder(#{__struct__ => _} = Struct, Encode) -> 'Elixir.JSONProtocol':encode(Struct, Encode);
encoder(Other, Encode) -> json:encode_value(Other, Encode).
```
encoder(nil, _Encode) -> <<"null">>;
encoder(null, _Encode) -> <<"\"null\"">>;
encoder(#{__struct__ => _} = Struct, Encode) -> 'Elixir.JSONProtocol':encode(Struct, Encode);
encoder(Other, Encode) -> json:encode_value(Other, Encode).

[1]: https://www.json.org/json-en.html
"Introducing JSON"
Expand Down

0 comments on commit adcbed2

Please sign in to comment.