Skip to content

Commit

Permalink
Merge pull request #779 from diml/fix-sexp-record-bug
Browse files Browse the repository at this point in the history
Fix sexp record bug
  • Loading branch information
rgrinberg authored May 17, 2018
2 parents 9fbfc27 + 9d3117d commit 03b5325
Show file tree
Hide file tree
Showing 4 changed files with 48 additions and 0 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,9 @@ next
- Add an `ignored_subdirs` stanza to replace `jbuild-ignore` files
(#767, @diml)

- Fix a bug where Dune ignored previous occurences of duplicated
fields (#779, @diml)

1.0+beta20 (10/04/2018)
-----------------------

Expand Down
2 changes: 2 additions & 0 deletions src/stdune/sexp.ml
Original file line number Diff line number Diff line change
Expand Up @@ -273,6 +273,8 @@ module Of_sexp = struct
| List (_, name_sexp :: values) -> begin
match name_sexp with
| Atom (_, A name) ->
if Name_map.mem acc name then
of_sexp_errorf sexp "Field %S is present too many times" name;
Name_map.add acc name { values; entry = sexp }
| List _ | Quoted_string _ ->
of_sexp_error name_sexp "Atom expected"
Expand Down
10 changes: 10 additions & 0 deletions test/unit-tests/dune
Original file line number Diff line number Diff line change
Expand Up @@ -69,3 +69,13 @@
(progn
(run ${exe:expect_test.exe} ${<})
(diff? ${<} ${<}.corrected))))))

(alias
((name runtest)
(deps (sexp.mlt
(glob_files ${SCOPE_ROOT}/src/.dune.objs/*.cmi)
(glob_files ${SCOPE_ROOT}/src/stdune/.stdune.objs/*.cmi)))
(action (chdir ${SCOPE_ROOT}
(progn
(run ${exe:expect_test.exe} ${<})
(diff? ${<} ${<}.corrected))))))
33 changes: 33 additions & 0 deletions test/unit-tests/sexp.mlt
Original file line number Diff line number Diff line change
@@ -0,0 +1,33 @@
(* -*- tuareg -*- *)
open Stdune;;
open Sexp.Of_sexp;;

let pp_sexp_ast ppf sexp =
Sexp.pp ppf (Sexp.Ast.remove_locs sexp)
;;
#install_printer pp_sexp_ast;;
[%%expect{|
val pp_sexp_ast : Format.formatter -> Stdune.Sexp.Ast.t -> unit = <fun>
|}]

Printexc.record_backtrace false;;
[%%expect{|
- : unit = ()
|}]

let sexp = Sexp.parse_string ~fname:"" ~mode:Single {|
((foo 1)
(foo 2))
|}
[%%expect{|
val sexp : Usexp.Ast.t = ((foo 1) (foo 2))
|}]

let of_sexp = record (field "foo" int)
let x = of_sexp sexp
[%%expect{|
val of_sexp : int Stdune.Sexp.Of_sexp.t = <fun>
Exception:
Stdune__Sexp.Of_sexp.Of_sexp (<abstr>,
"Field \"foo\" is present too many times", None).
|}]

0 comments on commit 03b5325

Please sign in to comment.