Skip to content

Commit

Permalink
Formatting
Browse files Browse the repository at this point in the history
  • Loading branch information
jonludlam committed Nov 14, 2024
1 parent 1da1bf0 commit dd9bb23
Show file tree
Hide file tree
Showing 3 changed files with 4 additions and 11 deletions.
3 changes: 1 addition & 2 deletions src/driver/odoc_units_of.ml
Original file line number Diff line number Diff line change
Expand Up @@ -215,8 +215,7 @@ let packages ~dirs ~extra_paths (pkgs : Packages.t list) : t list =
let name = md |> Fpath.rem_ext |> Fpath.basename |> ( ^ ) "page-" in
let lib_deps = Util.StringSet.empty in
let unit =
make_unit ~name ~kind ~rel_dir ~input_file:md ~pkg
~lib_deps
make_unit ~name ~kind ~rel_dir ~input_file:md ~pkg ~lib_deps
~enable_warnings:pkg.enable_warnings
in
[ unit ]
Expand Down
6 changes: 1 addition & 5 deletions src/odoc/resolver.ml
Original file line number Diff line number Diff line change
Expand Up @@ -70,10 +70,7 @@ end = struct
omit : Fs.Directory.t list;
}

type t = {
table : (string, pkg) Hashtbl.t;
current_root : named_root option;
}
type t = { table : (string, pkg) Hashtbl.t; current_root : named_root option }

type input = {
name : string;
Expand Down Expand Up @@ -543,7 +540,6 @@ let all_units ~library ({ libs; _ } : t) =
| Some libs ->
Odoc_utils.List.filter_map filter @@ all_roots ~root:library libs


type roots = {
page_roots : named_root list;
lib_roots : named_root list;
Expand Down
6 changes: 2 additions & 4 deletions src/odoc/resolver.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,10 +28,8 @@ type named_root = string * Fs.Directory.t
type roots = {
page_roots : named_root list;
lib_roots : named_root list;
current_lib : named_root option;
(** The current [-L]. *)
current_package : named_root option;
(** The current [-P]. *)
current_lib : named_root option; (** The current [-L]. *)
current_package : named_root option; (** The current [-P]. *)
current_dir : Fs.Directory.t;
(** Directory containing the output for the current unit. *)
}
Expand Down

0 comments on commit dd9bb23

Please sign in to comment.