Skip to content

Commit 38ba2e4

Browse files
committed
Rewrite some code with |>
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent e0c008d commit 38ba2e4

File tree

1 file changed

+25
-31
lines changed

1 file changed

+25
-31
lines changed

src/dune_rules/odoc.ml

Lines changed: 25 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -237,14 +237,11 @@ let odoc_include_flags ctx pkg requires =
237237
(let open Resolve.O in
238238
let+ libs = requires in
239239
let paths =
240-
libs
241-
|> List.fold_left
242-
~f:(fun paths lib ->
243-
match Lib.Local.of_lib lib with
244-
| None -> paths
245-
| Some lib ->
246-
Path.Set.add paths (Path.build (Paths.odocs ctx (Lib lib))))
247-
~init:Path.Set.empty
240+
List.fold_left libs ~init:Path.Set.empty ~f:(fun paths lib ->
241+
match Lib.Local.of_lib lib with
242+
| None -> paths
243+
| Some lib ->
244+
Path.Set.add paths (Path.build (Paths.odocs ctx (Lib lib))))
248245
in
249246
let paths =
250247
match pkg with
@@ -357,8 +354,8 @@ let setup_toplevel_index_rule sctx =
357354
| Some v -> sp {| <span class="version">%s</span>|} v
358355
in
359356
Some (sp "<li>%s%s</li>" link version_suffix))
357+
|> String.concat ~sep:"\n "
360358
in
361-
let list_items = String.concat ~sep:"\n " list_items in
362359
let html =
363360
sp
364361
{|<!DOCTYPE html>
@@ -586,13 +583,12 @@ let setup_package_aliases sctx (pkg : Package.t) =
586583
let dir = Path.Build.append_source ctx.build_dir pkg_dir in
587584
Alias.doc ~dir
588585
in
589-
Rules.Produce.Alias.add_deps alias
590-
(Action_builder.deps
591-
(Dep.html_alias ctx (Pkg name)
592-
:: (libs_of_pkg sctx ~pkg:name
593-
|> List.map ~f:(fun lib -> Dep.html_alias ctx (Lib lib)))
594-
|> Dune_engine.Dep.Set.of_list_map ~f:(fun f -> Dune_engine.Dep.alias f)
595-
))
586+
Dep.html_alias ctx (Pkg name)
587+
:: (libs_of_pkg sctx ~pkg:name
588+
|> List.map ~f:(fun lib -> Dep.html_alias ctx (Lib lib)))
589+
|> Dune_engine.Dep.Set.of_list_map ~f:(fun f -> Dune_engine.Dep.alias f)
590+
|> Action_builder.deps
591+
|> Rules.Produce.Alias.add_deps alias
596592

597593
let entry_modules_by_lib sctx lib =
598594
let info = Lib.Local.info lib in
@@ -670,9 +666,8 @@ let setup_package_odoc_rules_def =
670666
if String.Map.mem mlds "index" then
671667
Memo.Build.return mlds
672668
else
673-
let entry_modules = entry_modules ~pkg in
674669
let gen_mld = Paths.gen_mld_dir ctx pkg ++ "index.mld" in
675-
let* entry_modules = entry_modules sctx in
670+
let* entry_modules = entry_modules sctx ~pkg in
676671
let+ () =
677672
add_rule sctx
678673
(Action_builder.write_file gen_mld
@@ -701,19 +696,18 @@ let global_rules sctx =
701696
setup_package_aliases sctx pkg)
702697
in
703698
let* action =
704-
stanzas
705-
|> Memo.Build.List.concat_map ~f:(fun (w : _ Dir_with_dune.t) ->
706-
Memo.Build.List.filter_map w.data ~f:(function
707-
| Dune_file.Library (l : Dune_file.Library.t) -> (
708-
match l.visibility with
709-
| Public _ -> Memo.Build.return None
710-
| Private _ ->
711-
let scope = SC.find_scope_by_dir sctx w.ctx_dir in
712-
Library.best_name l
713-
|> Lib.DB.find_even_when_hidden (Scope.libs scope)
714-
>>| fun lib ->
715-
Option.value_exn lib |> Lib.Local.of_lib_exn |> Option.some)
716-
| _ -> Memo.Build.return None))
699+
Memo.Build.List.concat_map stanzas ~f:(fun (w : _ Dir_with_dune.t) ->
700+
Memo.Build.List.filter_map w.data ~f:(function
701+
| Dune_file.Library (l : Dune_file.Library.t) -> (
702+
match l.visibility with
703+
| Public _ -> Memo.Build.return None
704+
| Private _ ->
705+
let scope = SC.find_scope_by_dir sctx w.ctx_dir in
706+
Library.best_name l
707+
|> Lib.DB.find_even_when_hidden (Scope.libs scope)
708+
>>| fun lib ->
709+
Option.value_exn lib |> Lib.Local.of_lib_exn |> Option.some)
710+
| _ -> Memo.Build.return None))
717711
>>| Dune_engine.Dep.Set.of_list_map ~f:(fun (lib : Lib.Local.t) ->
718712
Lib lib |> Dep.html_alias ctx |> Dune_engine.Dep.alias)
719713
in

0 commit comments

Comments
 (0)