Skip to content

Commit

Permalink
Also detect --menhir flag
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Dec 15, 2023
1 parent 028cabc commit 0b46891
Show file tree
Hide file tree
Showing 2 changed files with 56 additions and 11 deletions.
23 changes: 12 additions & 11 deletions src/dune_rules/menhir/menhir_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -193,7 +193,7 @@ module Run (P : PARAMS) = struct
is the three-step process where Menhir is invoked twice and OCaml type
inference is performed in between. *)

let process3 base ~cmly (stanza : stanza) : unit Memo.t =
let process3 base ~cmly ~explain (stanza : stanza) : unit Memo.t =
let open Memo.O in
let expanded_flags = expand_flags stanza.flags in
(* 1. A first invocation of Menhir creates a mock [.ml] file. *)
Expand Down Expand Up @@ -234,7 +234,7 @@ module Run (P : PARAMS) = struct
let* () =
Module_compilation.ocamlc_i ~deps cctx mock_module ~output:(inferred_mli base)
in
let explain_flags = explain_flags base stanza.explain in
let explain_flags = explain_flags base (stanza.explain || explain) in
(* 3. A second invocation of Menhir reads the inferred [.mli] file. *)
menhir
[ Command.Args.dyn expanded_flags
Expand All @@ -254,9 +254,9 @@ module Run (P : PARAMS) = struct
(* [process3 stanza] converts a Menhir stanza into a set of build rules. This
is a simpler one-step process where Menhir is invoked directly. *)

let process1 base ~cmly (stanza : stanza) : unit Memo.t =
let process1 base ~cmly ~explain (stanza : stanza) : unit Memo.t =
let expanded_flags = expand_flags stanza.flags in
let explain_flags = explain_flags base stanza.explain in
let explain_flags = explain_flags base (stanza.explain || explain) in
menhir
[ Command.Args.dyn expanded_flags
; S explain_flags
Expand All @@ -278,22 +278,23 @@ module Run (P : PARAMS) = struct

let process (stanza : stanza) : unit Memo.t =
let base = Option.value_exn stanza.merge_into in
let ocaml_type_inference_disabled, cmly =
let ocaml_type_inference_disabled, cmly, explain =
Ordered_set_lang.Unexpanded.fold_strings
stanza.flags
~init:(false, false)
~f:(fun pos sw ((only_tokens, cmly) as acc) ->
~init:(false, false, false)
~f:(fun pos sw ((only_tokens, cmly, explain) as acc) ->
match pos with
| Neg -> acc
| Pos ->
(match String_with_vars.text_only sw with
| Some "--only-tokens" -> true, cmly
| Some "--cmly" -> only_tokens, true
| Some "--only-tokens" -> true, cmly, explain
| Some "--cmly" -> only_tokens, true, explain
| Some "--explain" -> only_tokens, cmly, true
| Some _ | None -> acc))
in
if ocaml_type_inference_disabled || not stanza.infer
then process1 base stanza ~cmly
else process3 base stanza ~cmly
then process1 base stanza ~cmly ~explain
else process3 base stanza ~cmly ~explain
;;

(* ------------------------------------------------------------------------ *)
Expand Down
44 changes: 44 additions & 0 deletions test/blackbox-tests/test-cases/menhir/explain.t
Original file line number Diff line number Diff line change
Expand Up @@ -84,6 +84,9 @@ Let's check that the conflicts file has been generated successfully:
START .





Let's check that it stops being generated if we remove the (explain) field:

$ cat >dune <<EOF
Expand All @@ -99,3 +102,44 @@ Let's check that it stops being generated if we remove the (explain) field:
Warning: in total, 1 production is never reduced.

$ ! test -f _build/default/parser.conflicts

Let's check that we can also generate the .conflicts file by passing the --explain flag directly:

$ cat >dune <<EOF
> (menhir (modules parser) (flags --explain))
> (library (name lib))
> EOF

$ dune build
Warning: one state has reduce/reduce conflicts.
Warning: one reduce/reduce conflict was arbitrarily resolved.
File "parser.mly", line 4, characters 15-20:
Warning: production start -> START is never reduced.
Warning: in total, 1 production is never reduced.

$ cat _build/default/parser.conflicts

** Conflict (reduce/reduce) in state 1.
** Token involved: #
** This state is reached from start after reading:

START

** The derivations that appear below have the following common factor:
** (The question mark symbol (?) represents the spot where the derivations begin to differ.)

start // lookahead token is inherited
(?)

** In state 1, looking ahead at #, reducing production
** start -> START
** is permitted because of the following sub-derivation:

START .

** In state 1, looking ahead at #, reducing production
** start -> START
** is permitted because of the following sub-derivation:

START .

0 comments on commit 0b46891

Please sign in to comment.