Skip to content

Commit e68af2d

Browse files
committed
Formatting
1 parent b38f0c5 commit e68af2d

File tree

6 files changed

+53
-37
lines changed

6 files changed

+53
-37
lines changed

src/driver/odoc.ml

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -62,16 +62,13 @@ let compile_md ~output_dir ~input_file:file ~parent_id =
6262
let _, f = Fpath.split_base file in
6363
Some Fpath.(output_dir // Id.to_fpath parent_id // set_ext "odoc" f)
6464
in
65-
let cmd =
66-
!odoc_md % Fpath.to_string file % "--output-dir" % p output_dir
67-
in
65+
let cmd = !odoc_md % Fpath.to_string file % "--output-dir" % p output_dir in
6866
let cmd = cmd % "--parent-id" % Id.to_string parent_id in
6967
let desc = Printf.sprintf "Compiling Markdown %s" (Fpath.to_string file) in
7068
let lines = Cmd_outputs.submit desc cmd output_file in
7169
Cmd_outputs.(
7270
add_prefixed_output cmd compile_output (Fpath.to_string file) lines)
7371

74-
7572
let compile_asset ~output_dir ~name ~parent_id =
7673
let open Cmd in
7774
let output_file =

src/driver/odoc.mli

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,8 @@ val compile :
2525
includes:Fpath.set ->
2626
parent_id:Id.t ->
2727
unit
28-
val compile_md : output_dir:Fpath.t -> input_file:Fpath.t -> parent_id:Id.t -> unit
28+
val compile_md :
29+
output_dir:Fpath.t -> input_file:Fpath.t -> parent_id:Id.t -> unit
2930

3031
val compile_asset : output_dir:Fpath.t -> name:string -> parent_id:Id.t -> unit
3132

src/driver/odoc_unit.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,7 @@ type impl_extra = { src_id : Odoc.Id.t; src_path : Fpath.t }
4444
type impl = [ `Impl of impl_extra ]
4545

4646
type mld = [ `Mld ]
47-
type md = [`Md]
47+
type md = [ `Md ]
4848
type asset = [ `Asset ]
4949

5050
type t = [ impl | intf | mld | asset | md ] unit

src/markdown/dune

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -3,4 +3,3 @@
33
(name odoc_md)
44
(package odoc-md)
55
(libraries cmarkit odoc.model odoc.odoc cmdliner))
6-

src/markdown/odoc_md.ml

Lines changed: 40 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
(* This exe will compile a markdown file, outputting a compiled `page-x.odoc` file.
1+
(* This exe will compile a markdown file, outputting a compiled `page-x.odoc` file.
22
This is tightly coupled with the internal representation of odoc files and thus needs
33
to be run with the exact same version of odoc that it is compiled with. *)
44

@@ -10,10 +10,13 @@ let parse id input_s =
1010
in
1111
let str = In_channel.(with_open_bin input_s input_all) in
1212
let content, _warnings = Doc_of_md.parse_comment ~location ~text:str () in
13-
let (content, ()) = Semantics.ast_to_comment ~internal_tags:Expect_none
14-
~sections_allowed:`All ~tags_allowed:true
15-
~parent_of_sections:(id :> Paths.Identifier.LabelParent.t) content []
16-
|> Error.raise_warnings in
13+
let content, () =
14+
Semantics.ast_to_comment ~internal_tags:Expect_none ~sections_allowed:`All
15+
~tags_allowed:true
16+
~parent_of_sections:(id :> Paths.Identifier.LabelParent.t)
17+
content []
18+
|> Error.raise_warnings
19+
in
1720
content
1821

1922
let mk_page input_s id content =
@@ -22,26 +25,35 @@ let mk_page input_s id content =
2225
let frontmatter, content = Comment.extract_frontmatter content in
2326
let digest = Digest.file input_s in
2427
let root =
25-
let file =
26-
Root.Odoc_file.create_page input_s zero_heading frontmatter
27-
in
28+
let file = Root.Odoc_file.create_page input_s zero_heading frontmatter in
2829
{ Root.id = (id :> Paths.Identifier.OdocId.t); file; digest }
2930
in
30-
let children=[] in
31-
{ Lang.Page.name=id; root; children; content; digest; linked = false; frontmatter }
31+
let children = [] in
32+
{
33+
Lang.Page.name = id;
34+
root;
35+
children;
36+
content;
37+
digest;
38+
linked = false;
39+
frontmatter;
40+
}
3241

3342
let run input_s parent_id_str odoc_dir =
3443
(* Construct the id of this page *)
35-
let page_name =
36-
Filename.basename input_s |> Filename.chop_extension
37-
in
44+
let page_name = Filename.basename input_s |> Filename.chop_extension in
3845
let parent_id = Odoc_odoc.Compile.mk_id parent_id_str in
39-
let id = Odoc_model.Paths.Identifier.Mk.leaf_page (parent_id, Odoc_model.Names.PageName.make_std page_name) in
46+
let id =
47+
Odoc_model.Paths.Identifier.Mk.leaf_page
48+
(parent_id, Odoc_model.Names.PageName.make_std page_name)
49+
in
4050

4151
let content = parse id input_s in
4252
let page = mk_page input_s id content in
4353

44-
let output = Fpath.(v odoc_dir // v parent_id_str / ("page-" ^ page_name ^ ".odoc")) in
54+
let output =
55+
Fpath.(v odoc_dir // v parent_id_str / ("page-" ^ page_name ^ ".odoc"))
56+
in
4557
Odoc_odoc.Odoc_file.save_page output ~warnings:[] page
4658

4759
open Cmdliner
@@ -51,24 +63,24 @@ let input =
5163
Arg.(required & pos 0 (some file) None & info ~doc ~docv:"FILE" [])
5264

5365
let parent_id =
54-
let doc = "Parent id. This defines both the location of the resulting odoc file as well as the \
55-
location of the eventual html or other file." in
66+
let doc =
67+
"Parent id. This defines both the location of the resulting odoc file as \
68+
well as the location of the eventual html or other file."
69+
in
5670
Arg.(
57-
required
58-
& opt (some string) None
59-
& info ~docv:"PARENT" ~doc [ "parent-id" ])
71+
required & opt (some string) None & info ~docv:"PARENT" ~doc [ "parent-id" ])
6072

6173
let output_dir =
62-
let doc = "Output file directory. The output file will be put in the parent-id path below this." in
74+
let doc =
75+
"Output file directory. The output file will be put in the parent-id path \
76+
below this."
77+
in
6378
Arg.(
64-
required
65-
& opt (some string) None
66-
& info ~docv:"PATH" ~doc [ "output-dir" ])
67-
79+
required & opt (some string) None & info ~docv:"PATH" ~doc [ "output-dir" ])
80+
6881
let cmd =
6982
let doc = "Compile a markdown file to an odoc page-*.odoc file." in
7083
let info = Cmd.info "odoc-md" ~doc in
71-
Cmd.v info
72-
Term.(const run $ input $ parent_id $ output_dir)
84+
Cmd.v info Term.(const run $ input $ parent_id $ output_dir)
7385

74-
let () = Cmdliner.(exit @@ Cmd.eval cmd)
86+
let () = Cmdliner.(exit @@ Cmd.eval cmd)

src/odoc/compile.ml

Lines changed: 9 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -261,7 +261,15 @@ let mld ~parent_id ~parents_children ~output ~children ~warnings_options input =
261261
in
262262
let page =
263263
Lang.Page.
264-
{ name=id; root; children; content; digest; linked = false; frontmatter }
264+
{
265+
name = id;
266+
root;
267+
children;
268+
content;
269+
digest;
270+
linked = false;
271+
frontmatter;
272+
}
265273
in
266274
Odoc_file.save_page output ~warnings:[] page;
267275
()
@@ -275,7 +283,6 @@ let mld ~parent_id ~parents_children ~output ~children ~warnings_options input =
275283
|> function
276284
| `Stop -> resolve [] (* TODO: Error? *)
277285
| `Docs content -> resolve content
278-
279286

280287
let handle_file_ext ext =
281288
match ext with

0 commit comments

Comments
 (0)