Skip to content

Commit

Permalink
fix(menhir): include_subdirs qualified
Browse files Browse the repository at this point in the history
menhir stanzas wouldn't know how to attach themselves to executables or
libraries with (include_subdirs qualified) because the module path
wouldn't be computed. Now we compute the module path and it works.

Signed-off-by: Rudi Grinberg <[email protected]>

<!-- ps-id: e4746ac6-cc95-4844-9fb9-25e9472b6fa0 -->
  • Loading branch information
rgrinberg committed Oct 16, 2023
1 parent d8b8b02 commit 6b0a82b
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 14 deletions.
11 changes: 10 additions & 1 deletion src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -248,10 +248,19 @@ let gen_rules_for_stanzas
| true ->
let* ml_sources = Dir_contents.ocaml dir_contents in
(match
let base_path =
Path.Local.descendant
(Path.Build.local ctx_dir)
~of_:(Path.Build.local (Dir_contents.dir dir_contents))
|> Option.value_exn
|> Path.Local.explode
|> List.map ~f:Module_name.of_string
in
Menhir_rules.module_names m
|> List.find_map ~f:(fun name ->
let open Option.O in
let* origin = Ml_sources.find_origin ml_sources name in
let path = base_path @ [ name ] in
let* origin = Ml_sources.find_origin ml_sources path in
List.find_map cctxs ~f:(fun (loc, cctx) ->
Option.some_if (Loc.equal loc (Ml_sources.Origin.loc origin)) cctx))
with
Expand Down
12 changes: 7 additions & 5 deletions src/dune_rules/ml_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ module Origin = struct
| Executables e -> e.buildable.loc
| Melange mel -> mel.loc
;;

let to_dyn = function
| Library _ -> Dyn.variant "Library" [ Dyn.Opaque ]
| Executables _ -> Dyn.variant "Executables" [ Dyn.Opaque ]
| Melange _ -> Dyn.variant "Melange" [ Dyn.Opaque ]
;;
end

module Modules = struct
Expand Down Expand Up @@ -265,11 +271,7 @@ let modules_and_obj_dir t ~for_ =
;;

let modules t ~for_ = modules_and_obj_dir t ~for_ |> fst

let find_origin (t : t) name =
(* TODO generalize to any path *)
Module_name.Path.Map.find t.modules.rev_map [ name ]
;;
let find_origin (t : t) path = Module_name.Path.Map.find t.modules.rev_map path

let virtual_modules ~lookup_vlib vlib =
let info = Lib.info vlib in
Expand Down
3 changes: 2 additions & 1 deletion src/dune_rules/ml_sources.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ module Origin : sig
| Melange of Melange_stanzas.Emit.t

val loc : t -> Loc.t
val to_dyn : t -> Dyn.t
end

module Artifacts : sig
Expand All @@ -38,7 +39,7 @@ val modules_and_obj_dir : t -> for_:for_ -> Modules.t * Path.Build.t Obj_dir.t
val modules : t -> for_:for_ -> Modules.t

(** Find out the origin of the stanza for a given module *)
val find_origin : t -> Module_name.t -> Origin.t option
val find_origin : t -> Module_name.Path.t -> Origin.t option

val empty : t

Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/top_module.ml
Original file line number Diff line number Diff line change
Expand Up @@ -33,7 +33,7 @@ let find_module sctx src =
let* dir_contents = drop_rules @@ fun () -> Dir_contents.get sctx ~dir in
let* ocaml = Dir_contents.ocaml dir_contents in
let stanza =
match Ml_sources.find_origin ocaml module_name with
match Ml_sources.find_origin ocaml [ module_name ] with
| Some (Executables exes) -> Some (`Executables exes)
| Some (Library lib) -> Some (`Library lib)
| None | Some (Melange _) -> None
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -17,9 +17,3 @@ Menhir in other places than the root of the file hierarchy.
Hint: Did you mean Baz?
[1]
$ test qualified
File "bar/dune", line 1, characters 0-23:
1 | (menhir
2 | (modules baz))
Error: I can't determine what library/executable the files produced by this
stanza are part of.
[1]

0 comments on commit 6b0a82b

Please sign in to comment.