Proto: tracing script translator.

This commit is contained in:
Benjamin Canou 2016-11-10 16:25:31 +01:00
parent 0f91192769
commit 1e2911dd94
6 changed files with 692 additions and 599 deletions

View File

@ -56,48 +56,47 @@ let parse_program s =
with with
| exn -> report_parse_error "program: " exn lexbuf | exn -> report_parse_error "program: " exn lexbuf
let rec print_ir ppf node = let rec print_ir locations ppf node =
let open Script in let open Script in
let rec do_seq = function let rec do_seq = function
| [] -> assert false | [] -> assert false
| [ last ] -> Format.fprintf ppf "%a }@]" print_ir last | [ last ] -> Format.fprintf ppf "%a }@]" (print_ir locations) last
| fst :: rest -> Format.fprintf ppf "%a ;@ " print_ir fst ; do_seq rest in | fst :: rest -> Format.fprintf ppf "%a ;@ " (print_ir locations) fst ; do_seq rest in
let rec do_args = function let rec do_args = function
| [] -> assert false | [] -> assert false
| [ last ] -> Format.fprintf ppf "%a@]" print_ir last | [ last ] -> Format.fprintf ppf "%a@]" (print_ir locations) last
| fst :: rest -> Format.fprintf ppf "%a@," print_ir fst ; do_args rest in | fst :: rest -> Format.fprintf ppf "%a@," (print_ir locations) fst ; do_args rest in
let print_location ppf loc =
if locations loc then begin
Format.fprintf ppf " /* %d */" loc
end in
match node with match node with
| String (_, s) -> Format.fprintf ppf "%S" s | String (_, s) -> Format.fprintf ppf "%S" s
| Int (_, s) -> Format.fprintf ppf "%s" s | Int (_, s) -> Format.fprintf ppf "%s" s
| Seq (_, [ one ]) -> print_ir ppf one | Seq (_, [ one ]) -> print_ir locations ppf one
| Seq (_, []) -> Format.fprintf ppf "{}" ; | Seq (_, []) -> Format.fprintf ppf "{}" ;
| Seq (_, seq) -> | Seq (_, seq) ->
Format.fprintf ppf "{ @[<v>" ; Format.fprintf ppf "{ @[<v>" ;
do_seq seq do_seq seq
| Prim (_, "push", [ Prim (_, name, []) ]) -> | Prim (loc, name, []) ->
Format.fprintf ppf "push %s" name Format.fprintf ppf "%s%a" name print_location loc
| Prim (_, name, []) -> | Prim (loc, name, seq) ->
Format.fprintf ppf "%s" name Format.fprintf ppf "@[<v 2>%s%a@," name print_location loc;
| Prim (_, "push", [ Prim (_, name, seq) ]) ->
Format.fprintf ppf "push @[<v 2>%s@," name ;
do_args seq
| Prim (_, name, seq) ->
Format.fprintf ppf "@[<v 2>%s@," name ;
do_args seq do_args seq
let print_program ppf c = let print_program locations ppf c =
Format.fprintf ppf Format.fprintf ppf
"@[<v 2>storage@,%a@]@." "@[<v 2>storage@,%a@]@."
print_ir (c : Script.code).Script.storage_type ; (print_ir (fun _ -> false)) (c : Script.code).Script.storage_type ;
Format.fprintf ppf Format.fprintf ppf
"@[<v 2>parameter@,%a@]@." "@[<v 2>parameter@,%a@]@."
print_ir (c : Script.code).Script.arg_type ; (print_ir (fun _ -> false)) (c : Script.code).Script.arg_type ;
Format.fprintf ppf Format.fprintf ppf
"@[<v 2>return@,%a@]@." "@[<v 2>return@,%a@]@."
print_ir (c : Script.code).Script.ret_type ; (print_ir (fun _ -> false)) (c : Script.code).Script.ret_type ;
Format.fprintf ppf Format.fprintf ppf
"@[<v 2>code@,%a@]" "@[<v 2>code@,%a@]"
print_ir (c : Script.code).Script.code (print_ir locations) (c : Script.code).Script.code
let parse_data s = let parse_data s =
let lexbuf = Lexing.from_string s in let lexbuf = Lexing.from_string s in
@ -121,7 +120,7 @@ module Program = Client_aliases.Alias (struct
type t = Script.code type t = Script.code
let encoding = Script.code_encoding let encoding = Script.code_encoding
let of_source s = parse_program s let of_source s = parse_program s
let to_source p = Lwt.return (Format.asprintf "%a" print_program p) let to_source p = Lwt.return (Format.asprintf "%a" (print_program (fun _ -> false)) p)
let name = "program" let name = "program"
end) end)
@ -169,8 +168,22 @@ let commands () =
(fun program () -> (fun program () ->
let open Data_encoding in let open Data_encoding in
Client_proto_rpcs.Helpers.typecheck_code (block ()) program >>= function Client_proto_rpcs.Helpers.typecheck_code (block ()) program >>= function
| Ok () -> | Ok type_map ->
message "Well typed" ; message "Well typed" ;
print_program
(fun l -> List.mem_assoc l type_map)
Format.std_formatter program ;
Format.printf "@." ;
List.iter
(fun (loc, (before, after)) ->
Format.printf
"%3d@[<v 0> : [ @[<v 0>%a ]@]@,-> [ @[<v 0>%a ]@]@]@."
loc
(Format.pp_print_list (print_ir (fun _ -> false)))
before
(Format.pp_print_list (print_ir (fun _ -> false)))
after)
type_map ;
Lwt.return () Lwt.return ()
| Error errs -> | Error errs ->
pp_print_error Format.err_formatter errs ; pp_print_error Format.err_formatter errs ;

View File

@ -11,8 +11,6 @@ val parse_program: string -> Script.code Lwt.t
val parse_data: string -> Script.expr Lwt.t val parse_data: string -> Script.expr Lwt.t
val parse_data_type: string -> Script.expr Lwt.t val parse_data_type: string -> Script.expr Lwt.t
val print_program: Format.formatter -> Script.code -> unit
module Program : Client_aliases.Alias with type t = Script.code module Program : Client_aliases.Alias with type t = Script.code
val commands: unit -> Cli_entries.command list val commands: unit -> Cli_entries.command list

View File

@ -92,7 +92,7 @@ end
module Helpers : sig module Helpers : sig
val minimal_time: val minimal_time:
block -> ?prio:int -> unit -> Time.t tzresult Lwt.t block -> ?prio:int -> unit -> Time.t tzresult Lwt.t
val typecheck_code: block -> Script.code -> unit tzresult Lwt.t val typecheck_code: block -> Script.code -> Script_ir_translator.type_map tzresult Lwt.t
val typecheck_tagged_data: block -> Script.expr -> unit tzresult Lwt.t val typecheck_tagged_data: block -> Script.expr -> unit tzresult Lwt.t
val typecheck_untagged_data: block -> Script.expr * Script.expr -> unit tzresult Lwt.t val typecheck_untagged_data: block -> Script.expr * Script.expr -> unit tzresult Lwt.t
val hash_data: block -> Script.expr -> string tzresult Lwt.t val hash_data: block -> Script.expr -> string tzresult Lwt.t

File diff suppressed because it is too large Load Diff

View File

@ -92,7 +92,7 @@ let update_locations ir =
(narg :: nargs, ni)) (narg :: nargs, ni))
([], succ i) args in ([], succ i) args in
(Seq (i, List.rev nargs), ni) in (Seq (i, List.rev nargs), ni) in
fst (update_locations 0 ir) fst (update_locations 1 ir)
let expr_encoding = let expr_encoding =
Data_encoding.conv Data_encoding.conv

View File

@ -331,7 +331,7 @@ module Helpers = struct
RPC.service RPC.service
~description: "Typecheck a piece of code in the current context" ~description: "Typecheck a piece of code in the current context"
~input: Script.code_encoding ~input: Script.code_encoding
~output: (wrap_tzerror empty) ~output: (wrap_tzerror Script_ir_translator.type_map_enc)
RPC.Path.(custom_root / "helpers" / "typecheck_code") RPC.Path.(custom_root / "helpers" / "typecheck_code")
let typecheck_tagged_data custom_root = let typecheck_tagged_data custom_root =