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
1922let 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
3342let 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
4759open Cmdliner
@@ -51,24 +63,24 @@ let input =
5163 Arg. (required & pos 0 (some file) None & info ~doc ~docv: " FILE" [] )
5264
5365let 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
6173let 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+
6881let 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)
0 commit comments