Client refactor: Move non-unix part of Data_Encoding_Ezjsonm into Data_Encoding.Json

This commit is contained in:
Grégoire Henry 2018-02-08 10:51:01 +01:00
parent c55181273c
commit 8c58d7a610
17 changed files with 79 additions and 74 deletions

View File

@ -452,7 +452,7 @@ let write fp cfg =
(Data_encoding.Json.construct encoding cfg)
let to_string cfg =
Data_encoding_ezjsonm.to_string
Data_encoding.Json.to_string
(Data_encoding.Json.construct encoding cfg)
let update

View File

@ -57,9 +57,9 @@ let encoding =
shell_header_encoding
(obj1 (req "data" Variable.bytes)))
let pp fmt op =
Format.pp_print_string fmt @@
Data_encoding_ezjsonm.to_string (Data_encoding.Json.construct encoding op)
let pp ppf op =
Data_encoding.Json.pp ppf
(Data_encoding.Json.construct encoding op)
let compare b1 b2 =
let (>>) x y = if x = 0 then y () else x in

View File

@ -15,32 +15,11 @@ let to_root = function
| `Null -> `O []
| oth -> `A [ oth ]
let to_string ?minify j = Ezjsonm.to_string ?minify (to_root j)
let pp = Json_repr.(pp (module Ezjsonm))
let from_string s =
try Ok (Ezjsonm.from_string s :> Data_encoding.json)
with Ezjsonm.Parse_error (_, msg) -> Error msg
let from_stream (stream: string Lwt_stream.t) =
let buffer = ref "" in
Lwt_stream.filter_map
(fun str ->
buffer := !buffer ^ str ;
try
let json = Ezjsonm.from_string !buffer in
buffer := "" ;
Some (Ok json)
with Ezjsonm.Parse_error _ ->
None)
stream
let write_file file json =
let json = to_root json in
protect begin fun () ->
Lwt_io.with_file ~mode:Output file begin fun chan ->
let str = to_string json in
let str = Data_encoding.Json.to_string ~minify:false json in
Lwt_io.write chan str >>= fun _ ->
return ()
end
@ -53,6 +32,3 @@ let read_file file =
return (Ezjsonm.from_string str :> Data_encoding.json)
end
end
let () =
Error_monad.json_to_string := to_string

View File

@ -9,20 +9,6 @@
open Error_monad
(** Read a JSON document from a string. *)
val from_string : string -> (Data_encoding.json, string) result
(** Read a stream of JSON documents from a stream of strings.
A single JSON document may be represented in multiple consecutive
strings. But only the first document of a string is considered. *)
val from_stream : string Lwt_stream.t -> (Data_encoding.json, string) result Lwt_stream.t
(** Write a JSON document to a string. This goes via an intermediate
buffer and so may be slow on large documents. *)
val to_string : ?minify:bool -> Data_encoding.json -> string
val pp : Format.formatter -> Data_encoding.json -> unit
(** Loads a JSON file in memory *)
val read_file : string -> Data_encoding.json tzresult Lwt.t

View File

@ -32,8 +32,8 @@ let encoding =
(obj1 (req "data" Variable.bytes)))
let pp fmt op =
Format.pp_print_string fmt @@
Data_encoding_ezjsonm.to_string (Data_encoding.Json.construct encoding op)
Data_encoding.Json.pp fmt
(Data_encoding.Json.construct encoding op)
let compare o1 o2 =
let (>>) x y = if x = 0 then y () else x in

View File

@ -51,8 +51,8 @@ let encoding =
(req "components" (list component_encoding)))
let pp ppf op =
Format.pp_print_string ppf @@
Data_encoding_ezjsonm.to_string (Data_encoding.Json.construct encoding op)
Data_encoding.Json.pp ppf
(Data_encoding.Json.construct encoding op)
let env_version_to_string = function
| V1 -> "V1"
@ -127,11 +127,11 @@ module Meta = struct
encoding
{ hash ; expected_env_version = env_version ; modules } in
Utils.write_file ~bin:false (dirname // name) @@
Data_encoding_ezjsonm.to_string config_file
Data_encoding.Json.to_string config_file
let of_file ~dir:dirname =
Utils.read_file ~bin:false (dirname // name) |>
Data_encoding_ezjsonm.from_string |> function
Data_encoding.Json.from_string |> function
| Error err -> Pervasives.failwith err
| Ok json -> Data_encoding.Json.destruct encoding json

View File

@ -98,7 +98,7 @@ module Cfg_file = struct
let write out cfg =
Utils.write_file ~bin:false out
(Data_encoding.Json.construct encoding cfg |>
Data_encoding_ezjsonm.to_string)
Data_encoding.Json.to_string)
end
@ -202,7 +202,7 @@ let tls_switch =
let read_config_file config_file = match
Utils.read_file ~bin:false config_file
|> Data_encoding_ezjsonm.from_string
|> Data_encoding.Json.from_string
with
| exception (Sys_error msg) ->
failwith
@ -229,7 +229,7 @@ let commands config_file cfg =
no_options
(fixed [ "config" ; "show" ])
(fun () (cctxt : Client_commands.full_context) ->
let pp_cfg ppf cfg = Format.fprintf ppf "%a" Data_encoding_ezjsonm.pp (Data_encoding.Json.construct Cfg_file.encoding cfg) in
let pp_cfg ppf cfg = Format.fprintf ppf "%a" Data_encoding.Json.pp (Data_encoding.Json.construct Cfg_file.encoding cfg) in
if not @@ Sys.file_exists config_file then
cctxt#warning
"@[<v 2>Warning: no config file at %s,@,\

View File

@ -135,7 +135,7 @@ let editor_fill_in ?(show_optionals=true) schema =
| Error msg -> Lwt.return (Error msg)
| Ok json ->
Lwt_io.(with_file ~mode:Output tmp (fun fp ->
write_line fp (Data_encoding_ezjsonm.to_string json))) >>= fun () ->
write_line fp (Data_encoding.Json.to_string json))) >>= fun () ->
edit ()
and edit () =
(* launch the user's editor on it *)
@ -163,7 +163,7 @@ let editor_fill_in ?(show_optionals=true) schema =
and reread () =
(* finally reread the file *)
Lwt_io.(with_file ~mode:Input tmp (fun fp -> read fp)) >>= fun text ->
match Data_encoding_ezjsonm.from_string text with
match Data_encoding.Json.from_string text with
| Ok r -> Lwt.return (Ok r)
| Error msg -> Lwt.return (Error (Printf.sprintf "bad input: %s" msg))
and delete () =
@ -394,7 +394,7 @@ let call raw_url (cctxt : #Client_commands.full_context) =
let call_with_json raw_url json (cctxt: Client_commands.full_context) =
let uri = Uri.of_string raw_url in
match Data_encoding_ezjsonm.from_string json with
match Data_encoding.Json.from_string json with
| Error err ->
cctxt#error
"Failed to parse the provided json: %s\n%!"

View File

@ -467,6 +467,33 @@ module Json = struct
type t = json
let to_root = function
| `O ctns -> `O ctns
| `A ctns -> `A ctns
| `Null -> `O []
| oth -> `A [ oth ]
let to_string ?minify j = Ezjsonm.to_string ?minify (to_root j)
let pp = Json_repr.(pp (module Ezjsonm))
let from_string s =
try Ok (Ezjsonm.from_string s :> json)
with Ezjsonm.Parse_error (_, msg) -> Error msg
let from_stream (stream: string Lwt_stream.t) =
let buffer = ref "" in
Lwt_stream.filter_map
(fun str ->
buffer := !buffer ^ str ;
try
let json = Ezjsonm.from_string !buffer in
buffer := "" ;
Some (Ok json)
with Ezjsonm.Parse_error _ ->
None)
stream
end
module Bson = struct

View File

@ -453,6 +453,20 @@ module Json : sig
val cannot_destruct : ('a, Format.formatter, unit, 'b) format4 -> 'a
val wrap_error : ('a -> 'b) -> 'a -> 'b
(** Read a JSON document from a string. *)
val from_string : string -> (json, string) result
(** Read a stream of JSON documents from a stream of strings.
A single JSON document may be represented in multiple consecutive
strings. But only the first document of a string is considered. *)
val from_stream : string Lwt_stream.t -> (json, string) result Lwt_stream.t
(** Write a JSON document to a string. This goes via an intermediate
buffer and so may be slow on large documents. *)
val to_string : ?minify:bool -> json -> string
val pp : Format.formatter -> json -> unit
end
module Bson : sig

View File

@ -3,7 +3,10 @@
(library
((name tezos_data_encoding)
(public_name tezos-data-encoding)
(libraries (tezos-stdlib ocplib-json-typed ocplib-json-typed.bson))
(libraries (tezos-stdlib
ocplib-json-typed
ocplib-json-typed.bson
ezjsonm))
(flags (:standard -w -9+27-30-32-40@8
-safe-string
-open Tezos_stdlib))))

View File

@ -11,9 +11,10 @@ depends: [
"jbuilder" { build & >= "1.0+beta17" }
"tezos-test-helpers" { test }
"tezos-stdlib"
"ezjsonm"
"js_of_ocaml" # for ocplib-json-typed.bson
"ocplib-json-typed"
"ocplib-endian"
"js_of_ocaml"
]
build: [
[ "jbuilder" "build" "-p" name "-j" jobs ]

View File

@ -490,9 +490,8 @@ let catch_closed_pipe f =
| Error _ | Ok _ as v -> Lwt.return v
let pp_json encoding ppf msg =
Format.pp_print_string ppf
(Data_encoding_ezjsonm.to_string
(Data_encoding.Json.construct encoding msg))
Data_encoding.Json.pp ppf
(Data_encoding.Json.construct encoding msg)
let write { writer ; conn } msg =
catch_closed_pipe begin fun () ->

View File

@ -269,7 +269,7 @@ let handle_error meth uri (body, media, _) f =
match media with
| Some ("application", "json") | None -> begin
Cohttp_lwt.Body.to_string body >>= fun body ->
match Data_encoding_ezjsonm.from_string body with
match Data_encoding.Json.from_string body with
| Ok body -> return (f (Some body))
| Error msg ->
request_failed meth uri
@ -287,13 +287,13 @@ let handle_error meth uri (body, media, _) f =
let generic_json_call ?logger ?body meth uri : (Data_encoding.json, Data_encoding.json option) rest_result Lwt.t =
let body =
Option.map body ~f:begin fun b ->
(Cohttp_lwt.Body.of_string (Data_encoding_ezjsonm.to_string b))
(Cohttp_lwt.Body.of_string (Data_encoding.Json.to_string b))
end in
let media = Media_type.json in
generic_call meth ?logger ~accept:Media_type.[bson ; json] ?body ~media uri >>=? function
| `Ok (body, (Some ("application", "json") | None), _) -> begin
Cohttp_lwt.Body.to_string body >>= fun body ->
match Data_encoding_ezjsonm.from_string body with
match Data_encoding.Json.from_string body with
| Ok json -> return (`Ok json)
| Error msg ->
request_failed meth uri

View File

@ -13,7 +13,7 @@ let json = {
name = Cohttp.Accept.MediaType ("application", "json") ;
q = Some 1000 ;
pp = begin fun _enc ppf raw ->
match Data_encoding_ezjsonm.from_string raw with
match Data_encoding.Json.from_string raw with
| Error err ->
Format.fprintf ppf
"@[Invalid JSON:@ \
@ -21,14 +21,14 @@ let json = {
\ - @[<v 2>Raw data:@ %s@]@]"
err raw
| Ok json ->
Data_encoding_ezjsonm.pp ppf json
Data_encoding.Json.pp ppf json
end ;
construct = begin fun enc v ->
Data_encoding_ezjsonm.to_string ~minify:true @@
Data_encoding.Json.to_string ~minify:true @@
Data_encoding.Json.construct enc v
end ;
destruct = begin fun enc body ->
match Data_encoding_ezjsonm.from_string body with
match Data_encoding.Json.from_string body with
| Error _ as err -> err
| Ok json ->
try Ok (Data_encoding.Json.destruct enc json)
@ -56,7 +56,7 @@ let bson = {
(module Json_repr_bson.Repr)
(module Json_repr.Ezjsonm)
bson in
Data_encoding_ezjsonm.pp ppf json
Data_encoding.Json.pp ppf json
end ;
construct = begin fun enc v ->
Bytes.unsafe_to_string @@
@ -86,7 +86,7 @@ let octet_stream = {
| Some v ->
Format.fprintf ppf
";; binary equivalent of the following json@.%a"
Data_encoding_ezjsonm.pp (Data_encoding.Json.construct enc v)
Data_encoding.Json.pp (Data_encoding.Json.construct enc v)
end ;
construct = begin fun enc v ->
MBytes.to_string @@

View File

@ -181,6 +181,5 @@ let cfg : _ P2p.message_config = { encoding ; versions }
let raw_encoding = P2p.Raw.encoding encoding
let pp_json ppf msg =
Format.pp_print_string ppf
(Data_encoding_ezjsonm.to_string
(Data_encoding.Json.construct raw_encoding (Message msg)))
Data_encoding.Json.pp ppf
(Data_encoding.Json.construct raw_encoding (Message msg))

View File

@ -90,7 +90,7 @@ module Account = struct
let pp_account ppf account =
let json = Data_encoding.Json.construct encoding account in
Format.fprintf ppf "%s" (Data_encoding_ezjsonm.to_string json)
Format.fprintf ppf "%s" (Data_encoding.Json.to_string json)
let create ?keys alias =
let sk, pk = match keys with
@ -122,7 +122,7 @@ module Account = struct
let pp_destination ppf destination =
let json = Data_encoding.Json.construct destination_encoding destination in
Format.fprintf ppf "%s" (Data_encoding_ezjsonm.to_string json)
Format.fprintf ppf "%s" (Data_encoding.Json.to_string json)
let create_destination ~alias ~contract ~pk =
let pkh = Ed25519.Public_key.hash pk in