Skip to content

Commit 692a497

Browse files
authored
Revert "Fix difference between bootstrap & dune behaviour w.r.t include-subdirs ambiguity"
1 parent c468e55 commit 692a497

File tree

4 files changed

+8
-78
lines changed

4 files changed

+8
-78
lines changed

src/dune_rules/modules.ml

Lines changed: 2 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -410,9 +410,7 @@ module Group = struct
410410
fun acc modules m -> loop acc modules (Module.path m)
411411
;;
412412

413-
(* [parents acc modules m] returns [acc] followed by all parent groups of
414-
module [m], ordered from innermost to outermost parent. *)
415-
let parents (t : t) m = parents_modules [ t ] t.modules m |> List.rev
413+
let parents (t : t) m = parents_modules [ t ] t.modules m
416414

417415
module Memo_traversals = struct
418416
let rec parallel_map ({ alias; modules; name = _ } as t) ~f =
@@ -487,10 +485,7 @@ module Group = struct
487485
Ok (if Module_name.equal name (Module.name li) then [ li ] else [])
488486
| _ ->
489487
(* TODO don't recompute this *)
490-
let parents =
491-
parents_modules [ t ] t.modules of_
492-
|> List.map ~f:(fun g -> g.modules, Some g.name)
493-
in
488+
let parents = parents t of_ |> List.map ~f:(fun g -> g.modules, Some g.name) in
494489
Find_dep.find_dep_of_parents parents name
495490
;;
496491

test/blackbox-tests/test-cases/boot/include-subdirs-qualified-ambiguous.t

Lines changed: 0 additions & 34 deletions
This file was deleted.

test/blackbox-tests/test-cases/include-qualified/ambiguous-module-name.t

Lines changed: 0 additions & 31 deletions
This file was deleted.

test/blackbox-tests/test-cases/merlin/include-subdirs-qualified.t

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -97,7 +97,7 @@
9797
(S $TESTCASE_ROOT/groupintf)
9898
(S $TESTCASE_ROOT/utils)
9999
(FLG (-w @1..3@5[email protected]@[email protected]@[email protected]@67@69-40 -strict-sequence -strict-formats -short-paths -keep-locs -g))
100-
(FLG (-open Foo -open Foo__Groupintf__))
100+
(FLG (-open Foo__Groupintf__ -open Foo))
101101
(UNIT_NAME foo__Groupintf__Calc))
102102
Calc: _build/default/groupintf/calc.ml
103103
((INDEX $TESTCASE_ROOT/_build/default/.foo.objs/cctx.ocaml-index)
@@ -109,7 +109,7 @@
109109
(S $TESTCASE_ROOT/groupintf)
110110
(S $TESTCASE_ROOT/utils)
111111
(FLG (-w @1..3@5[email protected]@[email protected]@[email protected]@67@69-40 -strict-sequence -strict-formats -short-paths -keep-locs -g))
112-
(FLG (-open Foo -open Foo__Groupintf__))
112+
(FLG (-open Foo__Groupintf__ -open Foo))
113113
(UNIT_NAME foo__Groupintf__Calc))
114114
Groupintf: _build/default/groupintf/groupintf
115115
((INDEX $TESTCASE_ROOT/_build/default/.foo.objs/cctx.ocaml-index)
@@ -121,7 +121,7 @@
121121
(S $TESTCASE_ROOT/groupintf)
122122
(S $TESTCASE_ROOT/utils)
123123
(FLG (-w @1..3@5[email protected]@[email protected]@[email protected]@67@69-40 -strict-sequence -strict-formats -short-paths -keep-locs -g))
124-
(FLG (-open Foo -open Foo__Groupintf__))
124+
(FLG (-open Foo__Groupintf__ -open Foo))
125125
(UNIT_NAME foo__Groupintf))
126126
Groupintf: _build/default/groupintf/groupintf.ml
127127
((INDEX $TESTCASE_ROOT/_build/default/.foo.objs/cctx.ocaml-index)
@@ -133,7 +133,7 @@
133133
(S $TESTCASE_ROOT/groupintf)
134134
(S $TESTCASE_ROOT/utils)
135135
(FLG (-w @1..3@5[email protected]@[email protected]@[email protected]@67@69-40 -strict-sequence -strict-formats -short-paths -keep-locs -g))
136-
(FLG (-open Foo -open Foo__Groupintf__))
136+
(FLG (-open Foo__Groupintf__ -open Foo))
137137
(UNIT_NAME foo__Groupintf))
138138
Main: _build/default/main
139139
((INDEX $TESTCASE_ROOT/_build/default/.foo.objs/cctx.ocaml-index)
@@ -169,7 +169,7 @@
169169
(S $TESTCASE_ROOT/groupintf)
170170
(S $TESTCASE_ROOT/utils)
171171
(FLG (-w @1..3@5[email protected]@[email protected]@[email protected]@67@69-40 -strict-sequence -strict-formats -short-paths -keep-locs -g))
172-
(FLG (-open Foo -open Foo__Utils))
172+
(FLG (-open Foo__Utils -open Foo))
173173
(UNIT_NAME foo__Utils__Calc))
174174
Calc: _build/default/utils/calc.ml
175175
((INDEX $TESTCASE_ROOT/_build/default/.foo.objs/cctx.ocaml-index)
@@ -181,6 +181,6 @@
181181
(S $TESTCASE_ROOT/groupintf)
182182
(S $TESTCASE_ROOT/utils)
183183
(FLG (-w @1..3@5[email protected]@[email protected]@[email protected]@67@69-40 -strict-sequence -strict-formats -short-paths -keep-locs -g))
184-
(FLG (-open Foo -open Foo__Utils))
184+
(FLG (-open Foo__Utils -open Foo))
185185
(UNIT_NAME foo__Utils__Calc))
186186
$ dune ocaml merlin dump-config utils

0 commit comments

Comments
 (0)