-
Notifications
You must be signed in to change notification settings - Fork 456
Description
My parser is in a foo library, wrapped as Foo by Dune. With a particular grammar, Menhir prefixes a reference to my Ast module with Foo.. This is invalid because the parser itself is in the foo library .
Here is a minimal example:
.
├── ast.ml
├── dune
├── dune-project
└── parser.mly
parser.mly:
%token Return
%token Eof
%start <Ast.Block.t> block
%%
let block :=
| ~ = retstat; Eof; <Some>
let retstat :=
| Return; {[]}
%%ast.ml:
module Retstat = struct
type t = int list
[@@deriving eq,ord,show]
end
module Block = struct
type t = Retstat.t option
[@@deriving eq,ord,show]
enddune:
(menhir
(modules parser))
(library
(name foo))
dune-project:
(lang dune 1.10)
(using fmt 1.1 (enabled_for dune))
(using menhir 2.0)
This results in the following error:
> dune build @check
Module Parser in directory _build/default depends on Foo.
This doesn't make sense to me.
Foo is the main module of the library and is the only module exposed
outside of the library. Consequently, it should be the one depending
on all the other modules in the library.
Dune uses --infer-write-query and --infer-read-reply on Menhir to infer the types from the grammar. As expected, it also uses ocamlc.opt -short-paths -i ... to infer the types on the generated mock. However, the -short-paths option, added in #1743 to fix #1504, doesn't seem to be enough to avoid the unwanted reference to the enclosing Foo module.
I've derived a small example from the mock that Menhir generated:
let (xv_retstat, xv_block) =
let _f (retstat : 'tv_retstat) = (Some retstat : Ast.Block.t) in
(raise Not_found : 'tv_retstat * Ast.Block.t)This results in:
> ocamlc.opt -I .foo.objs/byte -open Foo -short-paths -i -impl parser__mock.ml.mock
val xv_retstat : Foo.Ast.Retstat.t
val xv_block : Ast.Block.t
Issue originally submitted at https://gitlab.inria.fr/fpottier/menhir/issues/26.