Skip to content

Commit

Permalink
Fix encoding of inline_tests
Browse files Browse the repository at this point in the history
Encode optional fields as records where optional keys that are None will be
omitted in the resultant sexp. This will match reading the keys back with field_o
  • Loading branch information
rgrinberg committed Mar 18, 2018
1 parent 2bdbb3b commit 342f949
Show file tree
Hide file tree
Showing 4 changed files with 29 additions and 15 deletions.
15 changes: 7 additions & 8 deletions src/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -89,14 +89,13 @@ module Backend = struct
let lib x = string (Lib.name x) in
let f x = string (Lib.name x.lib) in
((1, 0),
record
[ "runner_libraries", list lib (Result.ok_exn t.runner_libraries)
; "flags" , Ordered_set_lang.Unexpanded.sexp_of_t
t.info.flags
; "generate_runner" , option Action.Unexpanded.sexp_of_t
t.info.generate_runner
; "extends" , option (list f)
(Option.map t.extends ~f:Result.ok_exn)
record_fields
[ field "runner_libraries" (list lib)
(Result.ok_exn t.runner_libraries)
; field "flags" Ordered_set_lang.Unexpanded.sexp_of_t t.info.flags
; field_o "generate_runner" Action.Unexpanded.sexp_of_t
t.info.generate_runner
; field_o "extends" (list f) (Option.map t.extends ~f:Result.ok_exn)
])
end
include M
Expand Down
9 changes: 9 additions & 0 deletions src/sexp.ml
Original file line number Diff line number Diff line change
Expand Up @@ -104,6 +104,15 @@ module To_sexp = struct
string_map f
(Hashtbl.foldi h ~init:String_map.empty ~f:(fun key data acc ->
String_map.add acc key data))

type field = string * Usexp.t option

let field name f v = (name, Some (f v))
let field_o name f v = (name, Option.map ~f v)

let record_fields (l : field list) =
List (List.filter_map l ~f:(fun (k, v) ->
Option.map v ~f:(fun v -> List[Atom (Atom.of_string k); v])))
end

module Of_sexp = struct
Expand Down
7 changes: 7 additions & 0 deletions src/sexp.mli
Original file line number Diff line number Diff line change
Expand Up @@ -46,6 +46,13 @@ module To_sexp : sig
include Combinators with type 'a t = 'a -> t

val record : (string * sexp) list -> sexp

type field

val field : string -> 'a t -> 'a -> field
val field_o : string -> 'a t-> 'a option -> field

val record_fields : field list t
end with type sexp := t

module Of_sexp : sig
Expand Down
13 changes: 6 additions & 7 deletions test/blackbox-tests/test-cases/inline_tests/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -34,12 +34,11 @@
-diff-cmd
-))
(generate_runner
((progn
(echo "let () = print_int 41")
(echo "\n")
(echo "let () = print_int 42")
(echo "\n")
(echo "let () = print_int 43;;"))))
(extends ())))))
(progn
(echo "let () = print_int 41")
(echo "\n")
(echo "let () = print_int 42")
(echo "\n")
(echo "let () = print_int 43;;")))))))
run alias dune-file/runtest
414243

0 comments on commit 342f949

Please sign in to comment.