Data_encoding: reorder and reorganize doc

This commit is contained in:
Raphaël Proust 2018-05-03 13:52:30 +08:00
parent 56fbc5267d
commit 2418554f78
2 changed files with 386 additions and 568 deletions

View File

@ -6,156 +6,8 @@
(* All rights reserved. No warranty, explicit or implicit, provided. *)
(* *)
(**************************************************************************)
module Encoding: sig
type 'a t = 'a Encoding.t
type 'a encoding = 'a t
exception No_case_matched
exception Unexpected_tag of int
exception Duplicated_tag of int
exception Invalid_tag of int * [ `Uint8 | `Uint16 ]
exception Unexpected_enum of string * string list
val null : unit encoding
val empty : unit encoding
val unit : unit encoding
val constant : string -> unit encoding
val int8 : int encoding
val uint8 : int encoding
val int16 : int encoding
val uint16 : int encoding
val int31 : int encoding
val int32 : int32 encoding
val int64 : int64 encoding
val ranged_int : int -> int -> int encoding
val ranged_float : float -> float -> float encoding
val bool : bool encoding
val string : string encoding
val bytes : MBytes.t encoding
val float : float encoding
val option : 'a encoding -> 'a option encoding
val result : 'a encoding -> 'b encoding -> ('a, 'b) result encoding
val string_enum : (string * 'a) list -> 'a encoding
val is_obj : 'a encoding -> bool
val is_tup : 'a encoding -> bool
module Fixed : sig
val string : int -> string encoding
val bytes : int -> MBytes.t encoding
end
module Variable : sig
val string : string encoding
val bytes : MBytes.t encoding
val array : 'a encoding -> 'a array encoding
val list : 'a encoding -> 'a list encoding
end
val dynamic_size : 'a encoding -> 'a encoding
val delayed : (unit -> 'a encoding) -> 'a encoding
type 'a field
val req :
?title:string -> ?description:string ->
string -> 't encoding -> 't field
val opt :
?title:string -> ?description:string ->
string -> 't encoding -> 't option field
val varopt :
?title:string -> ?description:string ->
string -> 't encoding -> 't option field
val dft :
?title:string -> ?description:string ->
string -> 't encoding -> 't -> 't field
val obj1 :
'f1 field -> 'f1 encoding
val obj2 :
'f1 field -> 'f2 field -> ('f1 * 'f2) encoding
val obj3 :
'f1 field -> 'f2 field -> 'f3 field -> ('f1 * 'f2 * 'f3) encoding
val obj4 :
'f1 field -> 'f2 field -> 'f3 field -> 'f4 field ->
('f1 * 'f2 * 'f3 * 'f4) encoding
val obj5 :
'f1 field -> 'f2 field -> 'f3 field -> 'f4 field -> 'f5 field ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5) encoding
val obj6 :
'f1 field -> 'f2 field -> 'f3 field -> 'f4 field -> 'f5 field ->
'f6 field ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6) encoding
val obj7 :
'f1 field -> 'f2 field -> 'f3 field -> 'f4 field -> 'f5 field ->
'f6 field -> 'f7 field ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7) encoding
val obj8 :
'f1 field -> 'f2 field -> 'f3 field -> 'f4 field -> 'f5 field ->
'f6 field -> 'f7 field -> 'f8 field ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7 * 'f8) encoding
val obj9 :
'f1 field -> 'f2 field -> 'f3 field -> 'f4 field -> 'f5 field ->
'f6 field -> 'f7 field -> 'f8 field -> 'f9 field ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7 * 'f8 * 'f9) encoding
val obj10 :
'f1 field -> 'f2 field -> 'f3 field -> 'f4 field -> 'f5 field ->
'f6 field -> 'f7 field -> 'f8 field -> 'f9 field -> 'f10 field ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7 * 'f8 * 'f9 * 'f10) encoding
val tup1 :
'f1 encoding ->
'f1 encoding
val tup2 :
'f1 encoding -> 'f2 encoding ->
('f1 * 'f2) encoding
val tup3 :
'f1 encoding -> 'f2 encoding -> 'f3 encoding ->
('f1 * 'f2 * 'f3) encoding
val tup4 :
'f1 encoding -> 'f2 encoding -> 'f3 encoding -> 'f4 encoding ->
('f1 * 'f2 * 'f3 * 'f4) encoding
val tup5 :
'f1 encoding -> 'f2 encoding -> 'f3 encoding -> 'f4 encoding ->
'f5 encoding ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5) encoding
val tup6 :
'f1 encoding -> 'f2 encoding -> 'f3 encoding -> 'f4 encoding ->
'f5 encoding -> 'f6 encoding ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6) encoding
val tup7 :
'f1 encoding -> 'f2 encoding -> 'f3 encoding -> 'f4 encoding ->
'f5 encoding -> 'f6 encoding -> 'f7 encoding ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7) encoding
val tup8 :
'f1 encoding -> 'f2 encoding -> 'f3 encoding -> 'f4 encoding ->
'f5 encoding -> 'f6 encoding -> 'f7 encoding -> 'f8 encoding ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7 * 'f8) encoding
val tup9 :
'f1 encoding -> 'f2 encoding -> 'f3 encoding -> 'f4 encoding ->
'f5 encoding -> 'f6 encoding -> 'f7 encoding -> 'f8 encoding ->
'f9 encoding ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7 * 'f8 * 'f9) encoding
val tup10 :
'f1 encoding -> 'f2 encoding -> 'f3 encoding -> 'f4 encoding ->
'f5 encoding -> 'f6 encoding -> 'f7 encoding -> 'f8 encoding ->
'f9 encoding -> 'f10 encoding ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7 * 'f8 * 'f9 * 'f10) encoding
val merge_objs : 'o1 encoding -> 'o2 encoding -> ('o1 * 'o2) encoding
val merge_tups : 'a1 encoding -> 'a2 encoding -> ('a1 * 'a2) encoding
val array : 'a encoding -> 'a array encoding
val list : 'a encoding -> 'a list encoding
val assoc : 'a encoding -> (string * 'a) list encoding
type 't case
type case_tag = Tag of int | Json_only
val case :
?name:string ->
case_tag ->
'a encoding -> ('t -> 'a option) -> ('a -> 't) -> 't case
val union :
?tag_size:[ `Uint8 | `Uint16 ] -> 't case list -> 't encoding
val describe :
?title:string -> ?description:string ->
't encoding ->'t encoding
val def : string -> 'a encoding -> 'a encoding
val conv :
('a -> 'b) -> ('b -> 'a) ->
?schema:Json_schema.schema ->
'b encoding -> 'a encoding
val mu : string -> ('a encoding -> 'a encoding) -> 'a encoding
val classify : 'a encoding -> [ `Fixed of int | `Dynamic | `Variable ]
val splitted : json:'a encoding -> binary:'a encoding -> 'a encoding
end = struct
module Encoding =
struct
include Encoding
let splitted ~json ~binary = raw_splitted ~json:(Json.convert json) ~binary
let assoc enc =
@ -166,67 +18,9 @@ end
include Encoding
module Json: sig
type json =
[ `O of (string * json) list
| `Bool of bool
| `Float of float
| `A of json list
| `Null
| `String of string ]
type t = json
type schema = Json_schema.schema
val encoding : json Encoding.t
val schema_encoding : schema Encoding.t
val convert : 'a Encoding.t -> 'a Json_encoding.encoding
val schema : 'a Encoding.t -> schema
val construct : 't Encoding.t -> 't -> json
val destruct : 't Encoding.t -> json -> 't
type path = path_item list
and path_item =
[ `Field of string
| `Index of int
| `Star
| `Next ]
exception Cannot_destruct of (path * exn)
exception Unexpected of string * string
exception No_case_matched of exn list
exception Bad_array_size of int * int
exception Missing_field of string
exception Unexpected_field of string
val print_error :
?print_unknown: (Format.formatter -> exn -> unit) ->
Format.formatter -> exn -> unit
val cannot_destruct : ('a, Format.formatter, unit, 'b) format4 -> 'a
val wrap_error : ('a -> 'b) -> 'a -> 'b
val from_string : string -> (json, string) result
val from_stream : string Lwt_stream.t -> (json, string) result Lwt_stream.t
val to_string : ?minify:bool -> json -> string
val pp : Format.formatter -> json -> unit
end = Json
module Bson: sig
type bson = Json_repr_bson.bson
type t = bson
val construct : 't encoding -> 't -> bson
val destruct : 't encoding -> bson -> 't
end = Bson
module Binary: sig
val length : 'a encoding -> 'a -> int
val read : 'a encoding -> MBytes.t -> int -> int -> (int * 'a) option
val write : 'a encoding -> 'a -> MBytes.t -> int -> int option
val to_bytes : 'a encoding -> 'a -> MBytes.t
val of_bytes : 'a encoding -> MBytes.t -> 'a option
val of_bytes_exn : 'a encoding -> MBytes.t -> 'a
val to_bytes_list : ?copy_blocks:bool -> int -> 'a encoding -> 'a -> MBytes.t list
type 'a status =
| Success of { res : 'a ; res_len : int ; remaining : MBytes.t list }
| Await of (MBytes.t -> 'a status)
| Error
val read_stream_of_bytes : ?init:MBytes.t list -> 'a encoding -> 'a status
val check_stream_of_bytes : ?init:MBytes.t list -> 'a encoding -> unit status
val fixed_length : 'a encoding -> int option
val fixed_length_exn : 'a encoding -> int
end = Binary
module Json = Json
module Bson = Bson
module Binary = Binary
type json = Json.t
let json = Json.encoding

View File

@ -11,7 +11,9 @@
(** {1 Data Encoding} *)
(** This module provides type-safe serialization and deserialization of
(** {2 Overview}
This module provides type-safe serialization and deserialization of
data structures. Backends are provided to both binary and JSON.
This works by writing type descriptors by hand, using the provided
@ -46,28 +48,31 @@
JSON operations are delegated to [ocplib-json-typed]. *)
(** The type for serializing or deserializing a value of type ['a]. *)
(** {2 Module structure}
This [Data_encoding] module provides muliple submodules:
- [Encoding] contains the necessary types and constructors for making the
type descriptors.
- [Json], [Bson], and [Binary] contain functions to serialize and
deserialize values.
*)
module Encoding: sig
(** The type descriptors for values of type ['a]. *)
type 'a t
type 'a encoding = 'a t
and 'a t
(** In memory JSON data, compatible with [Ezjsonm]. *)
type json =
[ `O of (string * json) list
| `Bool of bool
| `Float of float
| `A of json list
| `Null
| `String of string ]
type bson = Json_repr_bson.bson
type json_schema = Json_schema.schema
(** Exceptions that can be raised by the functions of this library. *)
exception No_case_matched
exception Unexpected_tag of int
exception Duplicated_tag of int
exception Invalid_tag of int * [ `Uint8 | `Uint16 ]
exception Unexpected_enum of string * string list
(** {3 Ground descriptors} *)
(** Special value [null] in JSON, nothing in binary. *)
val null : unit encoding
@ -117,6 +122,10 @@ val int64 : int64 encoding
*)
val ranged_int : int -> int -> int encoding
(** Encoding of floating point number
(encoded as a floating point number in JSON and a double in binary). *)
val float : float encoding
(** Float with bounds in a given range. Both bounds are inclusive *)
val ranged_float : float -> float -> float encoding
@ -134,9 +143,7 @@ val string : string encoding
(encoded via hex in JSON and directly as a sequence byte in binary). *)
val bytes : MBytes.t encoding
(** Encoding of floating point number
(encoded as a floating point number in JSON and a double in binary). *)
val float : float encoding
(** {3 Descriptor combinators} *)
(** Combinator to make an optional value
(represented as a 1-byte tag followed by the data (or nothing) in binary
@ -149,59 +156,28 @@ val option : 'a encoding -> 'a option encoding
encodings do not collide)). *)
val result : 'a encoding -> 'b encoding -> ('a, 'b) result encoding
(** Encode enumeration via association list
(represented as a string in JSON and binary). *)
val string_enum : (string * 'a) list -> 'a encoding
(** Is the given encoding serialized as a JSON object? *)
val is_obj : 'a encoding -> bool
(** Does the given encoding encode a tuple? *)
val is_tup : 'a encoding -> bool
(** Create encodings that produce data of a fixed length when binary encoded.
See the preamble for an explanation. *)
module Fixed : sig
(** Encode a fixed length string *)
val string : int -> string encoding
(** Encode a fixed length byte sequence *)
val bytes : int -> MBytes.t encoding
end
(** Create encodings that produce data of a variable length when binary encoded.
See the preamble for an explanation. *)
module Variable : sig
(** Encode a string *)
val string : string encoding
(** Encode a byte sequence *)
val bytes : MBytes.t encoding
(** Array encoding combinator *)
(** Array combinator. *)
val array : 'a encoding -> 'a array encoding
(** List encoding combinator *)
(** List combinator. *)
val list : 'a encoding -> 'a list encoding
end
(** Mark an encoding as being of dynamic size.
Forces the size to be stored alongside content when needed.
Usually used to fix errors from combining two encodings. *)
val dynamic_size : 'a encoding -> 'a encoding
(** Provide a transformer from one encoding to a different one.
(** Recompute the encoding definition each time it is used.
Useful for dynamically updating the encoding of values of an extensible
type via a global reference (e.g. exceptions). *)
val delayed : (unit -> 'a encoding) -> 'a encoding
Used to simplify nested encodings or to change the generic tuples
built by {obj1}, {tup1} and the like into proper records.
(** Encodes raw JSON data (BSON is used for binary). *)
val json : json encoding
A schema may optionally be provided as documentation of the new encoding. *)
val conv :
('a -> 'b) -> ('b -> 'a) ->
?schema:Json_schema.schema ->
'b encoding -> 'a encoding
(** Encodes a JSON schema (BSON encoded for binary). *)
val json_schema : json_schema encoding
(** Association list.
An object in JSON, a list of pairs in binary. *)
val assoc : 'a encoding -> (string * 'a) list encoding
(** {3 Product descriptors} *)
(** An enriched encoding to represent a component in a structured
type, augmenting the encoding with a name and whether it is a
@ -236,8 +212,7 @@ val dft :
?title:string -> ?description:string ->
string -> 't encoding -> 't -> 't field
(** {2 Constructors for objects with N fields} *)
(** {4 Constructors for objects with N fields} *)
(** These are serialized to binary by converting each internal object to binary
and placing them in the order of the original object.
These are serialized to JSON as a JSON object with the field names. *)
@ -275,12 +250,17 @@ val obj10 :
'f6 field -> 'f7 field -> 'f8 field -> 'f9 field -> 'f10 field ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7 * 'f8 * 'f9 * 'f10) encoding
(** {2 Constructors for tuples with N fields} *)
(** Create a larger object from the encodings of two smaller ones.
@raise invalid_arg if both arguments are not objects. *)
val merge_objs : 'o1 encoding -> 'o2 encoding -> ('o1 * 'o2) encoding
(** {4 Constructors for tuples with N fields} *)
(** These are serialized to binary by converting each internal object to binary
and placing them in the order of the original object.
These are serialized to JSON as JSON arrays/lists. *)
val tup1 :
'f1 encoding ->
'f1 encoding
@ -320,32 +300,18 @@ val tup10 :
'f9 encoding -> 'f10 encoding ->
('f1 * 'f2 * 'f3 * 'f4 * 'f5 * 'f6 * 'f7 * 'f8 * 'f9 * 'f10) encoding
(** {2 Combinators} *)
(** Create a larger object from the encodings of two smaller ones.
@raise invalid_arg if both arguments are not objects. *)
val merge_objs : 'o1 encoding -> 'o2 encoding -> ('o1 * 'o2) encoding
(** Create a large tuple encoding from two smaller ones.
@raise invalid_arg if both values are not tuples. *)
val merge_tups : 'a1 encoding -> 'a2 encoding -> ('a1 * 'a2) encoding
(** Array combinator. *)
val array : 'a encoding -> 'a array encoding
(** List combinator. *)
val list : 'a encoding -> 'a list encoding
(** Association list.
An object in JSON, a list of pairs in binary. *)
val assoc : 'a encoding -> (string * 'a) list encoding
(** {3 Sum descriptors} *)
(** A partial encoding to represent a case in a variant type. Hides
the (existentially bound) type of the parameter to the specific
case, providing its encoder, and converter functions to and from
the union type. *)
type 't case
type case_tag = Tag of int | Json_only
(** Encodes a variant constructor. Takes the encoding for the specific
@ -378,6 +344,58 @@ val case :
val union :
?tag_size:[ `Uint8 | `Uint16 ] -> 't case list -> 't encoding
(** {3 Predicates over descriptors} *)
(** Is the given encoding serialized as a JSON object? *)
val is_obj : 'a encoding -> bool
(** Does the given encoding encode a tuple? *)
val is_tup : 'a encoding -> bool
(** Classify an encoding wrt. its binary serialization as explained in the preamble. *)
val classify : 'a encoding -> [ `Fixed of int | `Dynamic | `Variable ]
(** {3 Specialized descriptors} *)
(** Encode enumeration via association list
(represented as a string in JSON and binary). *)
val string_enum : (string * 'a) list -> 'a encoding
(** Create encodings that produce data of a fixed length when binary encoded.
See the preamble for an explanation. *)
module Fixed : sig
val string : int -> string encoding
val bytes : int -> MBytes.t encoding
end
(** Create encodings that produce data of a variable length when binary encoded.
See the preamble for an explanation. *)
module Variable : sig
val string : string encoding
val bytes : MBytes.t encoding
val array : 'a encoding -> 'a array encoding
val list : 'a encoding -> 'a list encoding
end
(** Mark an encoding as being of dynamic size.
Forces the size to be stored alongside content when needed.
Usually used to fix errors from combining two encodings. *)
val dynamic_size : 'a encoding -> 'a encoding
(** Recompute the encoding definition each time it is used.
Useful for dynamically updating the encoding of values of an extensible
type via a global reference (e.g. exceptions). *)
val delayed : (unit -> 'a encoding) -> 'a encoding
(** Define different encodings for JSON and binary serialization. *)
val splitted : json:'a encoding -> binary:'a encoding -> 'a encoding
(** Combinator for recursive encodings. *)
val mu : string -> ('a encoding -> 'a encoding) -> 'a encoding
(** {3 Documenting descriptors} *)
(** Add documentation to an encoding. *)
val describe :
?title:string -> ?description:string ->
@ -386,37 +404,42 @@ val describe :
(** Give a name to an encoding. *)
val def : string -> 'a encoding -> 'a encoding
(** Provide a transformer from one encoding to a different one.
end
Used to simplify nested encodings or to change the generic tuples
built by {obj1}, {tup1} and the like into proper records.
A schema may optionally be provided as documentation of the new encoding. *)
val conv :
('a -> 'b) -> ('b -> 'a) ->
?schema:Json_schema.schema ->
'b encoding -> 'a encoding
(** Combinator for recursive encodings. *)
val mu : string -> ('a encoding -> 'a encoding) -> 'a encoding
include module type of Encoding with type 'a t = 'a Encoding.t
module Json: sig
(** In memory JSON data, compatible with [Ezjsonm]. *)
type json =
[ `O of (string * json) list
| `Bool of bool
| `Float of float
| `A of json list
| `Null
| `String of string ]
type t = json
type schema = Json_schema.schema
(** Encodes raw JSON data (BSON is used for binary). *)
val encoding : json Encoding.t
(** Encodes a JSON schema (BSON encoded for binary). *)
val schema_encoding : schema Encoding.t
(** Create a {!Json_encoding.encoding} from an {encoding}. *)
val convert : 'a encoding -> 'a Json_encoding.encoding
val convert : 'a Encoding.t -> 'a Json_encoding.encoding
(** Generate a schema from an {!encoding}. *)
val schema : 'a encoding -> json_schema
val schema : 'a Encoding.t -> schema
(** Construct a JSON object from an encoding. *)
val construct : 't encoding -> 't -> json
val construct : 't Encoding.t -> 't -> json
(** Destruct a JSON object into a value.
Fail with an exception if the JSON object and encoding do not match.. *)
val destruct : 't encoding -> json -> 't
val destruct : 't Encoding.t -> json -> 't
(** JSON Error. *)
@ -431,7 +454,8 @@ module Json : sig
| `Star
(** Any / every field or index. *)
| `Next
(** The next element after an array. *) ]
(** The next element after an array. *)
]
(** Exception raised by destructors, with the location in the original
JSON structure and the specific error. *)
@ -478,31 +502,26 @@ end
module Bson: sig
type t = Json_repr_bson.bson
type bson = Json_repr_bson.bson
type t = bson
(** Construct a BSON object from an encoding. *)
val construct : 't encoding -> 't -> bson
val construct : 't Encoding.t -> 't -> bson
(** Destruct a BSON object into a value.
Fail with an exception if the JSON object and encoding do not match.. *)
val destruct : 't encoding -> bson -> 't
val destruct : 't Encoding.t -> bson -> 't
end
(** Classify an encoding wrt. its binary serialization as explained in the preamble. *)
val classify : 'a encoding -> [ `Fixed of int | `Dynamic | `Variable ]
(** Define different encodings for JSON and binary serialization. *)
val splitted : json:'a encoding -> binary:'a encoding -> 'a encoding
module Binary: sig
val length : 'a encoding -> 'a -> int
val read : 'a encoding -> MBytes.t -> int -> int -> (int * 'a) option
val write : 'a encoding -> 'a -> MBytes.t -> int -> int option
val to_bytes : 'a encoding -> 'a -> MBytes.t
val of_bytes : 'a encoding -> MBytes.t -> 'a option
val of_bytes_exn : 'a encoding -> MBytes.t -> 'a
val length : 'a Encoding.t -> 'a -> int
val read : 'a Encoding.t -> MBytes.t -> int -> int -> (int * 'a) option
val write : 'a Encoding.t -> 'a -> MBytes.t -> int -> int option
val to_bytes : 'a Encoding.t -> 'a -> MBytes.t
val of_bytes : 'a Encoding.t -> MBytes.t -> 'a option
val of_bytes_exn : 'a Encoding.t -> MBytes.t -> 'a
(** [to_bytes_list ?copy_blocks blocks_size encod data] encode the
given data as a list of successive blocks of length
@ -512,7 +531,7 @@ module Binary : sig
can be garbage-collected only when all the blocks are
unreachable (because of the 'optimized' implementation of
MBytes.sub used internally *)
val to_bytes_list : ?copy_blocks:bool -> int -> 'a encoding -> 'a -> MBytes.t list
val to_bytes_list : ?copy_blocks:bool -> int -> 'a Encoding.t -> 'a -> MBytes.t list
(** This type is used when decoding binary data incrementally.
- In case of 'Success', the decoded data, the size of used data
@ -530,15 +549,20 @@ module Binary : sig
'Fixed' or a 'Dynamic' size, otherwise an exception
'Invalid_argument "streaming data with variable size"' is
raised *)
val read_stream_of_bytes : ?init:MBytes.t list -> 'a encoding -> 'a status
val read_stream_of_bytes : ?init:MBytes.t list -> 'a Encoding.t -> 'a status
(** Like read_stream_of_bytes, but only checks that the stream can
be read. Note that this is an approximation because failures
that may come from conversion functions present in encodings are
not checked *)
val check_stream_of_bytes : ?init:MBytes.t list -> 'a encoding -> unit status
val fixed_length : 'a encoding -> int option
val fixed_length_exn : 'a encoding -> int
val check_stream_of_bytes : ?init:MBytes.t list -> 'a Encoding.t -> unit status
val fixed_length : 'a Encoding.t -> int option
val fixed_length_exn : 'a Encoding.t -> int
end
type json = Json.t
val json: json Encoding.t
type json_schema = Json.schema
val json_schema: json_schema Encoding.t
type bson = Bson.t