Skip to content

Commit

Permalink
Small refactor of Antichain.check
Browse files Browse the repository at this point in the history
  • Loading branch information
panglesd committed Nov 4, 2024
1 parent f5f0687 commit e3b10bf
Show file tree
Hide file tree
Showing 2 changed files with 16 additions and 23 deletions.
29 changes: 11 additions & 18 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ module Antichain = struct
Fpath.normalize p

(** Check that a list of directories form an antichain: they are all disjoints *)
let check l =
let check ~opt l =
let l =
List.map
~f:(fun p -> p |> Fs.Directory.to_fpath |> absolute_normalization)
Expand All @@ -81,7 +81,12 @@ module Antichain = struct
rest
&& check rest
in
check l
if check l then Ok ()
else
let msg =
Format.sprintf "Paths given to all %s options must be disjoint" opt
in
Error (`Msg msg)
end

let docs = "ARGUMENTS"
Expand Down Expand Up @@ -467,14 +472,8 @@ module Indexing = struct
occurrences =
let marshall = if json then `JSON else `Marshall in
output_file ~dst marshall >>= fun output ->
(if not (Antichain.check (page_roots |> List.map ~f:snd)) then
Error (`Msg "Paths given to all -P options must be disjoint")
else Ok ())
>>= fun () ->
(if not (Antichain.check (lib_roots |> List.map ~f:snd)) then
Error (`Msg "Paths given to all -L options must be disjoint")
else Ok ())
>>= fun () ->
Antichain.check (page_roots |> List.map ~f:snd) ~opt:"-P" >>= fun () ->
Antichain.check (lib_roots |> List.map ~f:snd) ~opt:"-L" >>= fun () ->
Indexing.compile marshall ~output ~warnings_options ~occurrences ~lib_roots
~page_roots ~inputs_in_file ~odocls:inputs
let cmd =
Expand Down Expand Up @@ -641,14 +640,8 @@ end = struct
current_package warnings_options open_modules =
let input = Fs.File.of_string input_file in
let output = get_output_file ~output_file ~input in
(if not (Antichain.check (page_roots |> List.map ~f:snd)) then
Error (`Msg "Arguments given to -P cannot be included in each others")
else Ok ())
>>= fun () ->
(if not (Antichain.check (lib_roots |> List.map ~f:snd)) then
Error (`Msg "Arguments given to -L cannot be included in each others")
else Ok ())
>>= fun () ->
Antichain.check (page_roots |> List.map ~f:snd) ~opt:"-P" >>= fun () ->
Antichain.check (lib_roots |> List.map ~f:snd) ~opt:"-L" >>= fun () ->
let current_lib = current_library_of_input lib_roots input in
find_current_package ~current_package page_roots input
>>= fun current_package ->
Expand Down
10 changes: 5 additions & 5 deletions test/parent_id/parent_id.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ Testing the collision detection:

Same directory used twice
$ odoc link -P pkg:_odoc/pkg -P pkg2:_odoc/pkg _odoc/pkg/page-file.odoc
ERROR: Arguments given to -P cannot be included in each others
ERROR: Paths given to all -P options must be disjoint
[1]

# Two directories given relatively
Expand All @@ -23,7 +23,7 @@ Same directory used twice
$ odoc link -P pkg:_odoc/pkg/ -P pkg2:_odoc/pkg2/ _odoc/pkg/page-file.odoc
Wrong input:
$ odoc link -P pkg:_odoc/pkg -P pkg2:_odoc/pkg _odoc/pkg/page-file.odoc
ERROR: Arguments given to -P cannot be included in each others
ERROR: Paths given to all -P options must be disjoint
[1]

# Two directories given relatively with -L
Expand All @@ -38,23 +38,23 @@ Same directory used twice
$ odoc link -P pkg:_odoc/pkg/ -P pkg2:$PWD/_odoc/pkg2 _odoc/pkg/page-file.odoc
Wrong input
$ odoc link -P pkg:_odoc/pkg/ -P pkg2:$PWD/_odoc/pkg _odoc/pkg/page-file.odoc
ERROR: Arguments given to -P cannot be included in each others
ERROR: Paths given to all -P options must be disjoint
[1]

# Two directories given absolutely
Right input
$ odoc link -P pkg:$PWD/_odoc/pkg/ -P pkg2:$PWD/_odoc/pkg2 _odoc/pkg/page-file.odoc
Wrong input
$ odoc link -P pkg:$PWD/_odoc/pkg/ -P pkg2:$PWD/_odoc/pkg _odoc/pkg/page-file.odoc
ERROR: Arguments given to -P cannot be included in each others
ERROR: Paths given to all -P options must be disjoint
[1]

# With a bit of relative faff
Right input:
$ odoc link -P pkg:_odoc/../_odoc/pkg/ -P pkg2:_odoc/../_odoc/pkg2 _odoc/pkg/page-file.odoc
Wrong input:
$ odoc link -P pkg:_odoc/../_odoc/pkg/ -P pkg2:_odoc/../_odoc/pkg _odoc/pkg/page-file.odoc
ERROR: Arguments given to -P cannot be included in each others
ERROR: Paths given to all -P options must be disjoint
[1]

Testing detection of package:
Expand Down

0 comments on commit e3b10bf

Please sign in to comment.