Skip to content

Commit ccb10b2

Browse files
Julowpanglesd
andcommitted
driver: Refactor Landing_pages to use Format
Util.write_file is refactored to be more suitable. Co-authored-by: Paul-Elliot <[email protected]>
1 parent 31f55ab commit ccb10b2

File tree

4 files changed

+51
-71
lines changed

4 files changed

+51
-71
lines changed

src/driver/compile.ml

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
(* compile *)
22

3+
open Bos
4+
35
type compiled = Odoc_unit.t
46

57
let mk_byhash (pkgs : Odoc_unit.t list) =
@@ -58,8 +60,7 @@ let unmarshal filename : partial =
5860
(fun () -> Marshal.from_channel ic)
5961

6062
let marshal (v : partial) filename =
61-
let p = Fpath.parent filename in
62-
Util.mkdir_p p;
63+
let _ = OS.Dir.create (Fpath.parent filename) |> Result.get_ok in
6364
let oc = open_out_bin (Fpath.to_string filename) in
6465
Fun.protect
6566
~finally:(fun () -> close_out oc)
@@ -69,10 +70,10 @@ let find_partials odoc_dir : Odoc_unit.intf Odoc_unit.unit Util.StringMap.t * _
6970
=
7071
let tbl = Hashtbl.create 1000 in
7172
let hashes_result =
72-
Bos.OS.Dir.fold_contents ~dotfiles:false ~elements:`Dirs
73+
OS.Dir.fold_contents ~dotfiles:false ~elements:`Dirs
7374
(fun p hashes ->
7475
let index_m = Fpath.( / ) p "index.m" in
75-
match Bos.OS.File.exists index_m with
76+
match OS.File.exists index_m with
7677
| Ok true ->
7778
let tbl', hashes' = unmarshal index_m in
7879
List.iter
@@ -220,7 +221,7 @@ let sherlodoc_index_one ~output_dir (index : Odoc_unit.index) =
220221
let rel_path = Fpath.(index.search_dir / "sherlodoc_db.js") in
221222
let dst = Fpath.(output_dir // rel_path) in
222223
let dst_dir, _ = Fpath.split_base dst in
223-
Util.mkdir_p dst_dir;
224+
let _ = OS.Dir.create dst_dir |> Result.get_ok in
224225
Sherlodoc.index ~format:`js ~inputs ~dst ();
225226
rel_path
226227

src/driver/dune

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -13,4 +13,5 @@
1313
opam-format
1414
logs
1515
logs.fmt
16-
eio_main))
16+
eio_main
17+
odoc_utils))

src/driver/landing_pages.ml

Lines changed: 30 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,16 @@
11
open Packages
22
open Odoc_unit
33

4+
let fpf = Format.fprintf
5+
46
let make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content
57
?(include_dirs = []) ~pkgname ~pkg_args () =
68
let input_file = Fpath.(mld_dir // rel_path / "index.mld") in
79
let odoc_file = Fpath.(odoc_dir // rel_path / "page-index.odoc") in
810
let odocl_file = Fpath.(odocl_dir // rel_path / "page-index.odocl") in
9-
let () = Util.write_file input_file (String.split_on_char '\n' content) in
11+
Util.with_out_to input_file (fun oc ->
12+
fpf (Format.formatter_of_out_channel oc) "%t@?" content)
13+
|> Result.get_ok;
1014
let parent_id = rel_path |> Odoc.Id.of_fpath in
1115
{
1216
parent_id;
@@ -23,25 +27,15 @@ let make_unit ~odoc_dir ~odocl_dir ~mld_dir ~output_dir rel_path ~content
2327
}
2428

2529
module PackageLanding = struct
26-
let content pkg =
27-
let title = Format.sprintf "{0 %s}\n" pkg.name in
28-
let documentation =
29-
match pkg.mlds with
30-
| _ :: _ ->
31-
Format.sprintf
32-
"{1 Documentation pages}\n\n\
33-
{{!/%s/doc/index}Documentation for %s}\n"
34-
pkg.name pkg.name
35-
| [] -> ""
36-
in
37-
let libraries =
38-
match pkg.libraries with
39-
| [] -> ""
40-
| _ :: _ ->
41-
Format.sprintf "{1 Libraries}\n\n{{!/%s/lib/index}Libraries for %s}\n"
42-
pkg.name pkg.name
43-
in
44-
title ^ documentation ^ libraries
30+
let content pkg ppf =
31+
fpf ppf "{0 %s}\n" pkg.name;
32+
if not (List.is_empty pkg.mlds) then
33+
fpf ppf
34+
"{1 Documentation pages}@\n@\n{{!/%s/doc/index}Documentation for %s}@\n"
35+
pkg.name pkg.name;
36+
if not (List.is_empty pkg.libraries) then
37+
fpf ppf "{1 Libraries}@\n@\n{{!/%s/lib/index}Libraries for %s}@\n"
38+
pkg.name pkg.name
4539

4640
let page ~odoc_dir ~odocl_dir ~mld_dir ~output_dir ~pkg =
4741
let content = content pkg in
@@ -54,16 +48,15 @@ module PackageLanding = struct
5448
end
5549

5650
module PackageList = struct
57-
let content all =
51+
let content all ppf =
5852
let sorted_packages =
5953
all |> List.sort (fun n1 n2 -> String.compare n1.name n2.name)
6054
in
61-
let title = "{0 List of all packages}\n" in
62-
let s_of_pkg pkg =
63-
Format.sprintf "- {{!/__driver/%s/index}%s}" pkg.name pkg.name
55+
fpf ppf "{0 List of all packages}@\n";
56+
let print_pkg pkg =
57+
fpf ppf "- {{!/__driver/%s/index}%s}@\n" pkg.name pkg.name
6458
in
65-
let pkg_ul = sorted_packages |> List.map s_of_pkg |> String.concat "\n" in
66-
title ^ pkg_ul
59+
List.iter print_pkg sorted_packages
6760

6861
let page ~mld_dir ~odoc_dir ~odocl_dir ~output_dir all =
6962
let content = content all in
@@ -77,16 +70,13 @@ module PackageList = struct
7770
end
7871

7972
module LibraryLanding = struct
80-
let content lib =
81-
let title = Format.sprintf "{0 %s}\n" lib.lib_name in
82-
let s_of_module m =
83-
if m.m_hidden then None
84-
else Some (Format.sprintf "- {!%s}" m.Packages.m_name)
73+
let content lib ppf =
74+
fpf ppf "{0 %s}@\n" lib.lib_name;
75+
let print_module m =
76+
if not m.m_hidden then fpf ppf "- {!%s}@\n" m.Packages.m_name
8577
in
86-
let modules =
87-
lib.modules |> List.filter_map s_of_module |> String.concat "\n"
88-
in
89-
title ^ modules
78+
List.iter print_module lib.modules
79+
9080
let page ~pkg ~odoc_dir ~odocl_dir ~mld_dir ~output_dir lib =
9181
let content = content lib in
9282
let rel_path = Fpath.(v pkg.name / "lib" / lib.lib_name) in
@@ -99,13 +89,12 @@ module LibraryLanding = struct
9989
end
10090

10191
module PackageLibLanding = struct
102-
let content pkg =
103-
let title = Format.sprintf "{0 %s}\n" pkg.name in
104-
let s_of_lib (lib : Packages.libty) =
105-
Format.sprintf "- {{!/%s/%s/index}%s}" pkg.name lib.lib_name lib.lib_name
92+
let content pkg ppf =
93+
fpf ppf "{0 %s}@\n" pkg.name;
94+
let print_lib (lib : Packages.libty) =
95+
fpf ppf "- {{!/%s/%s/index}%s}@\n" pkg.name lib.lib_name lib.lib_name
10696
in
107-
let libraries = pkg.libraries |> List.map s_of_lib |> String.concat "\n" in
108-
title ^ libraries
97+
List.iter print_lib pkg.libraries
10998

11099
let page ~pkg ~odoc_dir ~odocl_dir ~mld_dir ~output_dir =
111100
let content = content pkg in

src/driver/util.ml

Lines changed: 13 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
open Odoc_utils
12
open Bos
23

34
module StringSet = Set.Make (String)
@@ -17,29 +18,17 @@ let lines_of_process cmd =
1718
| Ok x -> x
1819
| Error (`Msg e) -> failwith ("Error: " ^ e)
1920

20-
let mkdir_p d =
21-
let segs =
22-
Fpath.segs (Fpath.normalize d) |> List.filter (fun s -> String.length s > 0)
23-
in
24-
let _ =
25-
List.fold_left
26-
(fun path seg ->
27-
let d = Fpath.(path // v seg) in
28-
try
29-
Unix.mkdir (Fpath.to_string d) 0o755;
30-
d
31-
with
32-
| Unix.Unix_error (Unix.EEXIST, _, _) -> d
33-
| exn -> raise exn)
34-
(Fpath.v ".") segs
35-
in
36-
()
37-
38-
let write_file filename lines =
39-
let dir = fst (Fpath.split_base filename) in
40-
mkdir_p dir;
41-
let oc = open_out (Fpath.to_string filename) in
42-
List.iter (fun line -> Printf.fprintf oc "%s\n" line) lines;
43-
close_out oc
21+
(** Opens a file for writing and calls [f]. The destination directory is created
22+
if needed. *)
23+
let with_out_to filename f =
24+
let open ResultMonad in
25+
OS.Dir.create (Fpath.parent filename) >>= fun _ ->
26+
OS.File.with_oc filename
27+
(fun oc () ->
28+
f oc;
29+
Ok ())
30+
()
31+
|> Result.join
32+
>>= fun () -> Ok ()
4433

4534
let cp src dst = assert (lines_of_process Cmd.(v "cp" % src % dst) = [])

0 commit comments

Comments
 (0)