Skip to content

Commit

Permalink
report cycles with slight overlap as before
Browse files Browse the repository at this point in the history
Signed-off-by: Arseniy Alekseyev <aalekseyev@janestreet.com>
  • Loading branch information
aalekseyev committed Mar 27, 2019
1 parent b263015 commit fbfe037
Show file tree
Hide file tree
Showing 4 changed files with 14 additions and 9 deletions.
6 changes: 5 additions & 1 deletion src/dag/dag.ml
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,11 @@ module Make(Value : Value) : S with type value := Value.t = struct
match IC.add_edge_or_detect_cycle g v w with
| IC.EdgeAdded -> ()
| IC.EdgeCreatesCycle compute_cycle ->
raise (Cycle (List.rev (compute_cycle ())))
raise (Cycle (
let path = (compute_cycle ()) in
assert (List.hd path == w);
assert (Option.value_exn (List.last path) == v);
List.rev path @ [ v ]))

let children node = node.info.deps

Expand Down
8 changes: 4 additions & 4 deletions test/blackbox-tests/test-cases/loop/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -13,16 +13,16 @@ does show a cycle.

$ dune build --display short result1
Dependency cycle between the following files:
_build/default/input
--> _build/default/result2
_build/default/result2
--> _build/default/input
--> _build/default/result2
[1]

$ dune build --display short result1 --debug-dependency-path
Dependency cycle between the following files:
_build/default/input
--> _build/default/result2
_build/default/result2
--> _build/default/input
--> _build/default/result2
-> required by result2
-> required by input
-> required by result1
Expand Down
7 changes: 4 additions & 3 deletions test/unit-tests/dag.mlt
Original file line number Diff line number Diff line change
Expand Up @@ -101,7 +101,8 @@ val node41 : node = (6: k=1) (child 4 1) []
]]]];
(2: k=1) (child 1 1) []]
- : string list option =
Some ["child 4 1"; "child 3 1"; "child 2 1"; "child 1 2"; "root"]
Some
["child 4 1"; "child 3 1"; "child 2 1"; "child 1 2"; "root"; "child 4 1"]
- : node =
(1: k=2) (root) [(3: k=2) (child 1 2) [(4: k=2) (child 2 1) [(5: k=2) (child 3 1) [
(6: k=2) (child 4 1) [
Expand Down Expand Up @@ -220,11 +221,11 @@ cycle_test `a
;;

[%%expect{|
- : int list = [23; 22; 21; 20; 14; 13; 12; 11]
- : int list = [23; 22; 21; 20; 14; 13; 12; 11; 23]
|}]
;;
cycle_test `b
;;
[%%expect{|
- : int list = [23; 22; 21; 20; 14; 13; 12; 11]
- : int list = [23; 22; 21; 20; 14; 13; 12; 11; 23]
|}]
2 changes: 1 addition & 1 deletion test/unit-tests/memoize.mlt
Original file line number Diff line number Diff line change
Expand Up @@ -168,7 +168,7 @@ with
!stack |> List.map ~f:(fun st -> Stack_frame.name st, Stack_frame.input st);;

[%%expect{|
- : int list option = Some [2; 1; 0]
- : int list option = Some [2; 1; 0; 2]
- : int = 4
- : (string * Sexp.t) list =
[("cycle", Atom "2"); ("cycle", Atom "1"); ("cycle", Atom "0");
Expand Down

0 comments on commit fbfe037

Please sign in to comment.