diff --git a/.github/workflows/build.yml b/.github/workflows/build.yml index 1d186a5779..1b157630c4 100644 --- a/.github/workflows/build.yml +++ b/.github/workflows/build.yml @@ -15,7 +15,7 @@ jobs: # - windows-latest Windows doesn't work yet ocaml-compiler: # Don't include every versions. OCaml-CI already covers that - - 4.12.x + - 4.14.x include: - os: ubuntu-latest # Enable coverage only on a single build send-coverage: true diff --git a/.ocamlformat-ignore b/.ocamlformat-ignore index 9ca498158a..660823cc49 100644 --- a/.ocamlformat-ignore +++ b/.ocamlformat-ignore @@ -1,10 +1,15 @@ src/document/*.cppo.ml +src/loader/*.cppo.ml src/loader/cmi.ml src/loader/cmi.mli src/loader/cmt.ml src/loader/cmti.ml src/loader/doc_attr.ml -src/loader/*.cppo.ml +src/loader/local_jmp.ml +src/loader/lookup_def.ml +src/loader/uid.ml +src/loader/uid.mli +src/syntax_highlighter/syntax_highlighter.ml src/model/*.cppo.ml src/html_support_files/*.ml test/xref2/lib/* diff --git a/CHANGES.md b/CHANGES.md index 7fc187d21e..245786ff10 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -1,3 +1,9 @@ +UNRELEASED +---------- + +Additions +- Source code rendering (@Julow, @panglesd, #909) + 2.2.0 ----- diff --git a/doc/driver.md b/doc/driver.md index 58ed05d5f0..8f27332c75 100644 --- a/doc/driver.md +++ b/doc/driver.md @@ -6,9 +6,12 @@ The document built here includes not only the documentation of `odoc` itself, bu docs for a subset of `odoc`'s dependent libraries to show how this may be done. For a much more complete and comprehensive use of `odoc`, see the [Voodoo project](https://github.com/ocaml-doc/voodoo), the tool that is being used to build the package docs for -[ocaml.org/packages](https://ocaml.org/packages). +[ocaml.org/packages](https://ocaml.org/packages). The information in this page is specific to +odoc version 2.3 or later. For earlier +versions see the `driver.md` or `driver.mld` files in the corresponding source distribution. -First we need to initialise MDX with some libraries and helpful values. + +First, we need to initialise MDX with some libraries and helpful values: ```ocaml env=e1 (* Prelude *) @@ -20,11 +23,12 @@ open Bos;; let (>>=) = Result.bind;; let (>>|=) m f = m >>= fun x -> Ok (f x);; let get_ok = function | Ok x -> x | Error (`Msg m) -> failwith m +let relativize p = Fpath.(v ".." // p) (* this driver is run from the [doc] dir *) ``` ## Desired Output -`odoc` produces output files (html or others) in a structured directory tree, so before running `odoc`, the structure of the output must be decided. For these docs, we want the following structure: +`odoc` produces output files (HTML or others) in a structured directory tree, so before running `odoc`, the structure of the output must be decided. For these docs, we want the following structure: - `odoc/index.html` : main page - `odoc/{odoc_for_authors.html,...}` : other documentation pages @@ -36,31 +40,51 @@ let get_ok = function | Ok x -> x | Error (`Msg m) -> failwith m - `odoc/deps/stdlib/Stdlib/index.html` : Module page for the module `Stdlib` - `odoc/deps/astring/index.html` : astring main page - `odoc/deps/...` : other dependencies +- `odoc/source/...` : rendered source files -The `odoc` model for achieving this is that we have *pages* (`.mld` files) that have *children* which are either *further pages* (`.mld` files) or *modules* (from `.cmti` files). This {{!page-parent_child_spec} parent/child relationship} is specified on the command line. Parent pages must be *compiled* by `odoc` before their children. Then compiling a page `mypage.mld` will produce the file `page-mypage.odoc`. +The `odoc` model for achieving this is that we have *pages* (`.mld` files) that have *children* which are either *further pages* (`.mld` files), *modules* (from `.cmti` files), or +*source trees*. This {{!page-parent_child_spec} parent/child relationship} is specified on the command line. Parent pages must be *compiled* by `odoc` before their children. Then compiling a page `mypage.mld` will produce the file `page-mypage.odoc`. In the example below, there will be a file `odoc.mld` that corresponds with the top-level directory `odoc/`. It will be compiled as follows: ```sh -odoc compile odoc.mld --child page-odoc_model --child deps ... +odoc compile odoc.mld --child page-odoc_model --child deps + --child src-source ... ``` The file `deps.mld` which corresponds with the sub-directory `odoc/deps/`, will be compiled as follows: ```sh -odoc compile deps.mld -I . --parent `odoc` --child page-stdlib --child page-astring ... +odoc compile deps.mld -I . --parent page-odoc --child page-stdlib --child page-astring ... ``` The file `odoc_model.mld` will have a child module `Odoc_model`. It will be compiled as follows: ```sh -odoc compile odoc_model.mld -I . --parent `odoc` --child module-Odoc_model +odoc compile odoc_model.mld -I . --parent page-odoc --child module-Odoc_model +``` + +The last type of page contains a list of paths to the source files that should be rendered as HTML. The output will be found as a tree underneath this page. This will be compiled in the following way: + + +```sh +odoc source-tree source.map -I . --parent page-odoc ``` -When compiling any `.mld` file, the parent and all children must be specified. Parents can only be pages from other `.mld` files, and children may be pages (from `.mld` files) or modules (from `.cmti`/`.cmt` or `.cmi` files). +where the first few lines of `source.map` are: + +``` +src/xref2/utils.ml +src/xref2/type_of.ml +src/xref2/tools.ml +``` + +indicating the desire for the rendered source of `utils.ml` to be found as the file `odoc/source/src/xref2/utils.ml.html`. + +When compiling any `.mld` file, the parent and all children must be specified. Parents can only be pages from other `.mld` files, and children may be pages (from `.mld` files) or modules (from `.cmti`,`.cmt`, or `.cmi` files). The parent page must exist before the child page is created, and it must have had the child specified when it was initially compiled. @@ -70,7 +94,9 @@ Using `odoc` is a three-phase process: 1. Compilation: `odoc compile` -This takes the output from the compiler in the form of `.cmti`, `.cmt`, or `.cmi` files (in order of preference), translates it into `odoc`'s internal format, and performs some initial expansion and resolution operations. For a given input `/path/to/file.cmti` it will output the file `/path/to/file.odoc` unless the `-o` option is used to override the output file. If there were `.cmi` dependencies required for OCaml to compile these files, then there will be equivalent `.odoc` dependencies needed for the `odoc compile` step. `odoc` will search for these dependencies in the paths specified with the `-I` directive on compilation. `odoc` provides a command to help with this: `odoc compile-deps`: +This takes as input either `.mld` files containing pure odoc markup, or the output from the compiler in the form of `.cmti`, `.cmt`, or `.cmi` files (in order of preference). For `.mld` files, this step simply translates them into `odoc`'s internal format and writes the corresponding file. For example, given the input `foobar.mld`, `odoc` will output `page-foobar.odoc`. There are no dependencies for compiling `.mld` files beyond the parent as outlined above. + +For modules, compilation is the point where `odoc` performs some initial expansion and resolution operations, a process that usually introduces dependencies. For a given input `/path/to/file.cmti` it will output the file `/path/to/file.odoc` unless the `-o` option is used to override the output file. If there were `.cmi` dependencies required for OCaml to compile a particular module, then there will be equivalent `.odoc` dependencies needed for the `odoc compile` step. `odoc` will search for these dependencies in the paths specified with the `-I` directive on compilation. `odoc` provides a command to help with this: `odoc compile-deps`. As an example we can run `odoc compile-deps` on the file `../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Compile.cmti`: @@ -84,11 +110,11 @@ Stdlib__uchar ab6f1df93abf9e800a3e0d1543523c96 Odoc_xref2__Compile e0d620d652a724705f7ed620dfe07be0 ``` -so we can see we will need to run `odoc compile` against several `Stdlib` modules before we can compile `odoc_xref2__Compile.cmti` +From this, we see it's necessary to run `odoc compile` against several `Stdlib` modules before we can compile `odoc_xref2__Compile.cmti` 1. Linking: `odoc link` -This takes the `odoc` files produced during the compilation step and performs the final steps of expansion and resolution. It is during this phase that all the references in the documentation comments are resolved. In order for these to be resolved, everything that is referenced must have been compiled already, and their `odoc` files must be on the +This takes the `odoc` files produced during the compilation step and performs the final steps of resolution for both pages and modules, and expansion for modules only. It is during this phase that all the references in the documentation comments are resolved. In order for these to be resolved, everything that is referenced must have been compiled already, and their `odoc` files must be on the include path as specified by the `-I` arguments to `odoc link`. In this example, we achieve that by compiling all modules and `.mld` files before linking anything. The output of the link step is an `odocl` file, which is in the same path as the original `odoc` file by default. @@ -110,18 +136,25 @@ Let's start with some functions to execute the three phases of `odoc`. Compiling a file with `odoc` requires a few arguments: the file to compile, an optional parent, a list of include paths, a list of children for `.mld` files, -and an output path. Include paths can be just `'.'`, and we can calculate the -output file from the input because all of the files are going into the same directory. +optional parent and name for source implementation, and an output path. Include +paths can be just `'.'`, and we can calculate the output file from the input +because all of the files are going into the same directory. Linking a file with `odoc` requires the input file and a list of include paths. As for compile, we will hard-code the include path. -Generating the HTML requires the input `odocl` file and an output path. We will hard-code the output path to be `html`. +Generating the HTML requires the input `odocl` file, an optional implementation +source file (passed via the `--source` argument), and an output path. We will +hard-code the output path to be `html/`. + +Using the `--source` argument with an `.odocl` file that was not compiled with +`--source-parent-file` and `--source-name` will result in an error, as will omitting `--source` when generating HTML of an `odocl` that was +compiled with `--source-parent-file` and `--source-name`. In all of these, we'll capture `stdout` and `stderr` so we can check it later. ```ocaml env=e1 -let odoc = Cmd.v "../src/odoc/bin/main.exe" +let odoc = Cmd.v "../src/odoc/bin/main.exe" (* This is the just-built odoc binary *) let compile_output = ref [ "" ] @@ -129,13 +162,21 @@ let link_output = ref [ "" ] let generate_output = ref [ "" ] +let commands = ref [ ] + +let run cmd = + let cmd_str = Cmd.to_string cmd in + commands := cmd_str :: !commands; + OS.Cmd.(run_out ~err:OS.Cmd.err_run_out cmd |> to_lines) |> get_ok + let add_prefixed_output cmd list prefix lines = if List.length lines > 0 then list := !list @ Bos.Cmd.to_string cmd :: List.map (fun l -> prefix ^ ": " ^ l) lines -let compile file ?parent ?(ignore_output = false) children = +let compile file ?parent ?(output_dir = Fpath.v "./") + ?(ignore_output = false) ?source_args children = let output_file = let ext = Fpath.get_ext file in let basename = Fpath.basename (Fpath.rem_ext file) in @@ -145,8 +186,18 @@ let compile file ?parent ?(ignore_output = false) children = | _ -> failwith ("bad extension: " ^ ext) in let open Cmd in + let source_args = + match source_args with + | None -> Cmd.empty + | Some (source_name, source_parent_file) -> + Cmd.( + v "--source-name" % p source_name % "--source-parent-file" + % p source_parent_file) + in let cmd = - odoc % "compile" % Fpath.to_string file % "-I" % "." % "-o" % output_file + odoc % "compile" % Fpath.to_string file %% source_args % "-I" % "." + % "-o" + % p (Fpath.( / ) output_dir output_file) |> List.fold_right (fun child cmd -> cmd % "--child" % child) children in let cmd = @@ -154,7 +205,7 @@ let compile file ?parent ?(ignore_output = false) children = | Some p -> cmd % "--parent" % ("page-\"" ^ p ^ "\"") | None -> cmd in - let lines = OS.Cmd.(run_out ~err:err_run_out cmd |> to_lines) |> get_ok in + let lines = run cmd in if not ignore_output then add_prefixed_output cmd compile_output (Fpath.to_string file) lines @@ -162,30 +213,33 @@ let link ?(ignore_output = false) file = let open Cmd in let cmd = odoc % "link" % p file % "-I" % "." in let cmd = if Fpath.to_string file = "stdlib.odoc" then cmd % "--open=\"\"" else cmd in - Format.printf "%a" pp cmd; - let lines = OS.Cmd.(run_out ~err:err_run_out cmd |> to_lines) |> get_ok in + let lines = run cmd in if not ignore_output then add_prefixed_output cmd link_output (Fpath.to_string file) lines -let html_generate ?(ignore_output = false) file = +let html_generate ?(ignore_output = false) file source = let open Cmd in + let source = match source with None -> empty | Some source -> v "--source" % p source in let cmd = - odoc % "html-generate" % p file % "-o" % "html" % "--theme-uri" % "odoc" + odoc % "html-generate" %% source % p file % "-o" % "html" % "--theme-uri" % "odoc" % "--support-uri" % "odoc" in - let lines = OS.Cmd.(run_out cmd ~err:err_run_out |> to_lines) |> get_ok in + let lines = run cmd in if not ignore_output then add_prefixed_output cmd generate_output (Fpath.to_string file) lines let support_files () = let open Cmd in let cmd = odoc % "support-files" % "-o" % "html/odoc" in - OS.Cmd.(run_out cmd |> to_lines) |> get_ok + run cmd ``` -We'll now make some library lists. We have not only external dependency libraries, but -[odoc] itself is also separated into libraries too. These two sets of libraries will be -documented in different sections, so we'll keep them in separate lists. +We'll now make some library lists. We have not only external dependency +libraries, but `odoc` itself is also separated into libraries. These two +sets of libraries will be documented in different sections, so we'll keep them +in separate lists. Moreover, `odoc` libraries will include the source code, via +a hardcoded path. + Additionally we'll also construct a list containing the extra documentation pages. Finally let's create a list mapping the section to its parent, which matches the hierarchy declared above. @@ -220,7 +274,7 @@ let dep_libraries = | _ -> dep_libraries_core let odoc_libraries = [ - "odoc_xref_test"; "odoc_xref2"; "odoc_odoc"; + "odoc_xref_test"; "odoc_xref2"; "odoc_odoc"; "odoc_html_support_files"; "odoc_model_desc"; "odoc_model"; "odoc_manpage"; "odoc_loader"; "odoc_latex"; "odoc_html"; "odoc_document"; "odoc_examples" ];; @@ -244,28 +298,41 @@ let parents = ``` -[odoc] operates on the compiler outputs. We need to find them for both the files compiled by Dune within this project and those in libraries we compile against. -The following uses `ocamlfind` to locate the library paths for our dependencies: +`odoc` operates on the compiler outputs. We need to find them for both the files compiled by Dune within this project and those in libraries we compile against. +The following uses `ocamlfind` to locate the library paths for our dependencies. Since `ocamlfind` gives +us the absolute path, we also have a short function here to relativize it based on our current working +directory to ensure the log of commands we collect is as reproducible as possible. ```ocaml env=e1 let ocamlfind = Cmd.v "ocamlfind" +let reach t ~from = + let rec loop t from = + match (t, from) with + | a :: t, b :: from when a = b -> loop t from + | _ -> List.fold_right (fun _ acc -> ".." :: acc) from t + in + let v s = String.split_on_char '/' s in + loop (v t) (v from) |> String.concat "/" + +let relativize_path = + let pwd = Sys.getcwd () in + fun p -> reach p ~from:pwd + let lib_path lib = let cmd = Cmd.(ocamlfind % "query" % lib) in - OS.Cmd.(run_out cmd |> to_lines >>|= List.hd) + run cmd |> List.hd |> relativize_path let lib_paths = List.fold_right (fun lib acc -> - acc >>= fun acc -> - lib_path lib >>|= fun l -> (lib, l) :: acc) - dep_libraries (Ok []) - |> get_ok + (lib, lib_path lib) :: acc) + dep_libraries [] ``` -We need a function to find `odoc` inputs given a search path. `odoc` -operates on [.cmti], [.cmt] or [.cmi] files, in order of preference, and the following -function finds all matching files given a search path. Then it returns an `Fpath.Set.t` +We need a function to find `odoc` inputs from the given search path. `odoc` +operates on `.cmti`, `.cmt`, or `.cmi` files, in order of preference, and the following +function finds all matching files starting from the given path. Then it returns an `Fpath.Set.t` that contains the `Fpath.t` values representing the absolute file path, without its extension. ```ocaml env=e1 @@ -296,7 +363,7 @@ let best_file base = |> List.find (fun f -> Bos.OS.File.exists f |> get_ok) ``` -Many of the units will be 'hidden' -- that is, their name will be mangled by Dune +Many of the units will be 'hidden', meaning that Dune will mangle their name in order to namespace them. This is achieved by prefixing the namespace module and a double underscore, so we can tell by the existence of a double underscore that a module is intended to be hidden. The following predicate tests for that condition: @@ -305,7 +372,6 @@ a module is intended to be hidden. The following predicate tests for that condit let is_hidden path = Astring.String.is_infix ~affix:"__" (Fpath.to_string path) ``` - To build the documentation, we start with these files. With the following function, we'll call `odoc compile-deps` on the file to find all other compilation units upon which it depends: @@ -314,15 +380,79 @@ type compile_deps = { digest : Digest.t; deps : (string * Digest.t) list } let compile_deps f = let cmd = Cmd.(odoc % "compile-deps" % Fpath.to_string f) in - OS.Cmd.(run_out cmd |> to_lines) - >>|= List.filter_map (Astring.String.cut ~sep:" ") - >>= fun l -> + let deps = run cmd in + let l = List.filter_map (Astring.String.cut ~sep:" ") deps in let basename = Fpath.(basename (f |> rem_ext)) |> String.capitalize_ascii in match List.partition (fun (n, _) -> basename = n) l with | [ (_, digest) ], deps -> Ok { digest; deps } | _ -> Error (`Msg "odd") ``` +For `odoc` libraries, we infer the implementation and interface source file path +from the library name. We list them in a file, passed to `odoc source-tree`, to +generate `src-source.odoc`. This file contains the source hierarchy, and will be +linked and passed to `html-generate` just as other pages and compilation units. + +It is used as the `source-parent` for all units for which we could provide +sources. + +```ocaml env=e1 +let source_tree_output = ref [ "" ] + +let source_tree ?(ignore_output = false) ~parent ~output file = + let open Cmd in + let parent = v "--parent" % ("page-\"" ^ parent ^ "\"") in + let cmd = odoc % "source-tree" % "-I" % "." %% parent % "-o" % p output % p file in + let lines = run cmd in + if not ignore_output then + add_prefixed_output cmd source_tree_output (Fpath.to_string file) lines + +let odoc_source_tree = Fpath.v "src-source.odoc" + +let source_dir_of_odoc_lib lib = + match String.split_on_char '_' lib with + | "odoc" :: s -> + let libname = Fpath.(v (String.concat "_" s)) in + Some Fpath.(v "src" // libname) + | _ -> None + +let source_files_of_odoc_module lib module_ = + let filename = + let module_ = + match Astring.String.cut ~rev:true ~sep:"__" module_ with + | None -> module_ + | Some (_, "") -> module_ + | Some (_, module_) -> module_ + in + (* ML.ml should not be renamed *) + if String.for_all (fun c -> Char.equal (Char.uppercase_ascii c) c) module_ + then module_ + else String.uncapitalize_ascii module_ + in + match source_dir_of_odoc_lib lib with + | None -> None + | Some relpath -> + let add_filename path ext = + Fpath.( / ) path filename |> Fpath.add_ext ext + in + let find_by_extension path exts = + exts + |> List.map (fun ext -> add_filename path ext) + |> List.find_opt (fun f -> Bos.OS.File.exists (relativize f) |> get_ok) + in + find_by_extension relpath [ "pp.ml"; "ml" ] + +let compile_source_tree units = + let sources = + List.filter_map (fun (_, _, _, file) -> Option.map Fpath.to_string file) units + in + let source_map = Fpath.v "source.map" in + let () = Bos.OS.File.write_lines source_map sources |> get_ok in + let () = source_tree ~parent:"odoc" ~output:odoc_source_tree source_map in + (odoc_source_tree, false, None) + +``` + Let's now put together a list of all possible modules. We'll keep track of which library they're in, and whether that library is a part of `odoc` or a dependency library. @@ -336,7 +466,11 @@ let odoc_units = Fpath.Set.fold (fun p acc -> if Astring.String.is_infix ~affix:lib (Fpath.to_string p) then - ("odoc", lib, p) :: acc + let impl = + let module_ = Fpath.basename p in + source_files_of_odoc_module lib module_ + in + ("odoc", lib, p, impl) :: acc else acc) odoc_all_unit_paths []) odoc_libraries @@ -348,7 +482,7 @@ let all_units = List.map (fun (lib, p) -> Fpath.Set.fold - (fun p acc -> ("deps", lib, p) :: acc) + (fun p acc -> ("deps", lib, p, None) :: acc) (find_units p |> get_ok) []) lib_paths in @@ -364,7 +498,7 @@ let compile_mlds () = let mkmld x = Fpath.(add_ext "mld" (v x)) in ignore (compile (mkmld "odoc") - ("page-deps" :: List.map mkpage (odoc_libraries @ extra_docs))); + ("src-source" :: "page-deps" :: List.map mkpage (odoc_libraries @ extra_docs))); ignore (compile (mkmld "deps") ~parent:"odoc" (List.map mkpage dep_libraries)); let extra_odocs = List.map @@ -379,7 +513,7 @@ let compile_mlds () = let parent = List.assoc library parents in let children = List.filter_map - (fun (parent, lib, child) -> + (fun (parent, lib, child, _) -> if lib = library then Some (Fpath.basename child |> mkmod) else None) all_units @@ -389,7 +523,7 @@ let compile_mlds () = all_libraries in List.map - (fun f -> (Fpath.v f, false)) + (fun f -> (Fpath.v f, false, None)) ("page-odoc.odoc" :: "page-deps.odoc" :: odocs @ extra_odocs) ``` @@ -398,7 +532,11 @@ Now we get to the compilation phase. For each unit, we query its dependencies, t ```ocaml env=e1 let compile_all () = let mld_odocs = compile_mlds () in - let rec rec_compile parent lib file = + let source_tree = compile_source_tree all_units in + let source_args = + Option.map (fun source_relpath -> (source_relpath, odoc_source_tree)) + in + let rec rec_compile ?impl parent lib file = let output = Fpath.(base (set_ext "odoc" file)) in if OS.File.exists output |> get_ok then [] else @@ -408,47 +546,51 @@ let compile_all () = (fun acc (dep_name, digest) -> match List.find_opt - (fun (_, _, f) -> + (fun (_, _, f, _) -> Fpath.basename f |> String.capitalize_ascii = dep_name) all_units with | None -> acc - | Some (parent, lib, dep_path) -> + | Some (parent, lib, dep_path, impl) -> let file = best_file dep_path in - rec_compile parent lib file @ acc) + rec_compile ?impl parent lib file @ acc) [] deps.deps in let ignore_output = parent = "deps" in - ignore (compile file ~parent:lib ~ignore_output []); - (output, ignore_output) :: files + let source_args = source_args impl in + compile file ~parent:lib ?source_args ~ignore_output []; + (output, ignore_output, impl) :: files in - List.fold_left - (fun acc (parent, lib, dep) -> acc @ rec_compile parent lib (best_file dep)) + source_tree + :: List.fold_left + (fun acc (parent, lib, dep, impl) -> + acc @ rec_compile ?impl parent lib (best_file dep)) [] all_units @ mld_odocs ``` -Linking is now straightforward. We only need to link non-hidden `odoc` files, as any hidden are almost certainly aliased inside the non-hidden ones (a result of namespacing usually, and these aliases will be expanded). +Linking is now straightforward. We link all `odoc` files. ```ocaml env=e1 let link_all odoc_files = - let not_hidden (f, _) = not (is_hidden f) in List.map - (fun (odoc_file, ignore_output) -> + (fun (odoc_file, ignore_output, source) -> ignore (link ~ignore_output odoc_file); - Fpath.set_ext "odocl" odoc_file) - (List.filter not_hidden odoc_files) + Fpath.set_ext "odocl" odoc_file, source) + odoc_files ``` Now we simply run `odoc html-generate` over all of the resulting `odocl` files. +This will generate sources, as well as documentation for non-hidden units. ```ocaml env=e1 let generate_all odocl_files = - List.iter (fun f -> ignore(html_generate f)) odocl_files; + let relativize_opt = function None -> None | Some file -> Some (relativize file) in + List.iter (fun (f, source) -> ignore(html_generate f (relativize_opt source))) odocl_files; support_files () ``` -The following code actually executes all of the above, and we're done! +The following code executes all of the above, and we're done! ```ocaml env=e1 let compiled = compile_all () in @@ -471,31 +613,2217 @@ Let's see if there was any output from the `odoc` invocations: "page-deps.odoc: File \"src/fpath.mli\", line 7, characters 59-71:"; "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(Set) Couldn't find \"Set\""; "page-deps.odoc: File \"src/fpath.mli\", line 7, characters 28-52:"; - "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(file_exts) Couldn't find \"file_exts\""; - "'../src/odoc/bin/main.exe' 'link' 'page-stdlib.odoc' '-I' '.'"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 199, characters 0-29:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Reg_with_debug_info) Parent_module: Lookup failure (root module): Reg_with_debug_info"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 198, characters 0-30:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Reg_availability_set) Parent_module: Lookup failure (root module): Reg_availability_set"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 194, characters 0-15:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Ratio) Parent_module: Lookup failure (root module): Ratio"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 159, characters 0-13:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Num) Parent_module: Lookup failure (root module): Num"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 158, characters 0-13:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Nat) Parent_module: Lookup failure (root module): Nat"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 76, characters 0-29:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Compute_ranges_intf) Parent_module: Lookup failure (root module): Compute_ranges_intf"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 75, characters 0-24:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Compute_ranges) Parent_module: Lookup failure (root module): Compute_ranges"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 24, characters 0-17:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Big_int) Parent_module: Lookup failure (root module): Big_int"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 21, characters 0-24:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Available_regs) Parent_module: Lookup failure (root module): Available_regs"; - "page-stdlib.odoc: File \"library_mlds/stdlib.mld\", line 9, characters 0-22:"; - "page-stdlib.odoc: Warning: Failed to resolve reference unresolvedroot(Arith_status) Parent_module: Lookup failure (root module): Arith_status"] + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(file_exts) Couldn't find \"file_exts\""] +# !source_tree_output;; +- : string list = [""] # !generate_output;; - : string list = [""; + "'../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/odoc_model.ml' 'odoc_model.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc'"; + "odoc_model.odocl: Warning, resolved hidden path: Odoc_model__.Paths_types.Identifier.source_dir_pv"; + "odoc_model.odocl: Warning, resolved hidden path: Odoc_model__.Paths_types.Identifier.source_dir"; + "odoc_model.odocl: Warning, resolved hidden path: Odoc_model__.Paths_types.Identifier.source_dir_pv"; "'../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc'"; "odoc_examples.odocl: Warning, resolved hidden path: Odoc_examples__.Unexposed.t"] ``` + +We can have a look at the produced hierarchy of files, which matches the desired output. Note that source files with a `.ml.html` extension are generated for modules compiled with the `--source` option. +```sh +$ ls html/odoc +contributing.html +deps +driver.html +dune.html +features.html +fonts +highlight.pack.js +index.html +interface.html +katex.min.css +katex.min.js +ocamldoc_differences.html +odoc.css +odoc_document +odoc_examples +odoc_for_authors.html +odoc_html +odoc_html_support_files +odoc_latex +odoc_loader +odoc_manpage +odoc_model +odoc_model_desc +odoc_odoc +odoc_xref2 +odoc_xref_test +parent_child_spec.html +source +$ ls html/odoc/deps +astring +biniou +cmdliner +fmt +fpath +index.html +odoc-parser +result +stdlib +tyxml +yojson +$ find html/odoc/deps | sort | tail -n 20 +html/odoc/deps/tyxml/Xml_wrap/module-type-T/index.html +html/odoc/deps/tyxml/index.html +html/odoc/deps/yojson +html/odoc/deps/yojson/Yojson +html/odoc/deps/yojson/Yojson/Basic +html/odoc/deps/yojson/Yojson/Basic/Util +html/odoc/deps/yojson/Yojson/Basic/Util/index.html +html/odoc/deps/yojson/Yojson/Basic/index.html +html/odoc/deps/yojson/Yojson/Lexer_state +html/odoc/deps/yojson/Yojson/Lexer_state/index.html +html/odoc/deps/yojson/Yojson/Raw +html/odoc/deps/yojson/Yojson/Raw/index.html +html/odoc/deps/yojson/Yojson/Safe +html/odoc/deps/yojson/Yojson/Safe/Util +html/odoc/deps/yojson/Yojson/Safe/Util/index.html +html/odoc/deps/yojson/Yojson/Safe/index.html +html/odoc/deps/yojson/Yojson/index.html +html/odoc/deps/yojson/Yojson_biniou +html/odoc/deps/yojson/Yojson_biniou/index.html +html/odoc/deps/yojson/index.html +$ find html/odoc/odoc_html | sort +html/odoc/odoc_html +html/odoc/odoc_html/Odoc_html +html/odoc/odoc_html/Odoc_html/Config +html/odoc/odoc_html/Odoc_html/Config/index.html +html/odoc/odoc_html/Odoc_html/Generator +html/odoc/odoc_html/Odoc_html/Generator/index.html +html/odoc/odoc_html/Odoc_html/Html_fragment_json +html/odoc/odoc_html/Odoc_html/Html_fragment_json/index.html +html/odoc/odoc_html/Odoc_html/Html_page +html/odoc/odoc_html/Odoc_html/Html_page/index.html +html/odoc/odoc_html/Odoc_html/Link +html/odoc/odoc_html/Odoc_html/Link/Path +html/odoc/odoc_html/Odoc_html/Link/Path/index.html +html/odoc/odoc_html/Odoc_html/Link/index.html +html/odoc/odoc_html/Odoc_html/Types +html/odoc/odoc_html/Odoc_html/Types/index.html +html/odoc/odoc_html/Odoc_html/index.html +html/odoc/odoc_html/index.html +``` + +Finally, let's have a list of all of the commands executed during the execution of this process: + +```ocaml env=e1 +# List.iter (Printf.printf "$ %s\n") (List.rev !commands);; +$ 'ocamlfind' 'query' 'biniou' +$ 'ocamlfind' 'query' 'yojson' +$ 'ocamlfind' 'query' 'stdlib' +$ 'ocamlfind' 'query' 'fmt' +$ 'ocamlfind' 'query' 'tyxml' +$ 'ocamlfind' 'query' 'result' +$ 'ocamlfind' 'query' 'fpath' +$ 'ocamlfind' 'query' 'cmdliner' +$ 'ocamlfind' 'query' 'astring' +$ 'ocamlfind' 'query' 'odoc-parser' +$ '../src/odoc/bin/main.exe' 'compile' 'odoc.mld' '-I' '.' '-o' './page-odoc.odoc' '--child' 'page-"ocamldoc_differences"' '--child' 'page-"dune"' '--child' 'page-"odoc_for_authors"' '--child' 'page-"interface"' '--child' 'page-"features"' '--child' 'page-"parent_child_spec"' '--child' 'page-"driver"' '--child' 'page-"contributing"' '--child' 'page-"interface"' '--child' 'page-"odoc_examples"' '--child' 'page-"odoc_document"' '--child' 'page-"odoc_html"' '--child' 'page-"odoc_latex"' '--child' 'page-"odoc_loader"' '--child' 'page-"odoc_manpage"' '--child' 'page-"odoc_model"' '--child' 'page-"odoc_model_desc"' '--child' 'page-"odoc_html_support_files"' '--child' 'page-"odoc_odoc"' '--child' 'page-"odoc_xref2"' '--child' 'page-"odoc_xref_test"' '--child' 'page-deps' '--child' 'src-source' +$ '../src/odoc/bin/main.exe' 'compile' 'deps.mld' '-I' '.' '-o' './page-deps.odoc' '--child' 'page-"biniou"' '--child' 'page-"yojson"' '--child' 'page-"stdlib"' '--child' 'page-"fmt"' '--child' 'page-"tyxml"' '--child' 'page-"result"' '--child' 'page-"fpath"' '--child' 'page-"cmdliner"' '--child' 'page-"astring"' '--child' 'page-"odoc-parser"' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'interface.mld' '-I' '.' '-o' './page-interface.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'contributing.mld' '-I' '.' '-o' './page-contributing.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'driver.mld' '-I' '.' '-o' './page-driver.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'parent_child_spec.mld' '-I' '.' '-o' './page-parent_child_spec.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'features.mld' '-I' '.' '-o' './page-features.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'interface.mld' '-I' '.' '-o' './page-interface.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'odoc_for_authors.mld' '-I' '.' '-o' './page-odoc_for_authors.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'dune.mld' '-I' '.' '-o' './page-dune.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'ocamldoc_differences.mld' '-I' '.' '-o' './page-ocamldoc_differences.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc-parser.mld' '-I' '.' '-o' './page-odoc-parser.odoc' '--child' 'module-Odoc_parser' '--child' 'module-Odoc_parser__' '--child' 'module-Odoc_parser__Ast' '--child' 'module-Odoc_parser__Lexer' '--child' 'module-Odoc_parser__Loc' '--child' 'module-Odoc_parser__Parse_error' '--child' 'module-Odoc_parser__Syntax' '--child' 'module-Odoc_parser__Token' '--child' 'module-Odoc_parser__Warning' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/astring.mld' '-I' '.' '-o' './page-astring.odoc' '--child' 'module-Astring' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/cmdliner.mld' '-I' '.' '-o' './page-cmdliner.odoc' '--child' 'module-Cmdliner' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/fpath.mld' '-I' '.' '-o' './page-fpath.odoc' '--child' 'module-Fpath' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/result.mld' '-I' '.' '-o' './page-result.odoc' '--child' 'module-Result' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/tyxml.mld' '-I' '.' '-o' './page-tyxml.odoc' '--child' 'module-Html_f' '--child' 'module-Html_sigs' '--child' 'module-Html_types' '--child' 'module-Svg_f' '--child' 'module-Svg_sigs' '--child' 'module-Svg_types' '--child' 'module-Xml_iter' '--child' 'module-Xml_print' '--child' 'module-Xml_sigs' '--child' 'module-Xml_stream' '--child' 'module-Xml_wrap' '--child' 'module-Tyxml' '--child' 'module-Tyxml_html' '--child' 'module-Tyxml_svg' '--child' 'module-Tyxml_xml' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/fmt.mld' '-I' '.' '-o' './page-fmt.odoc' '--child' 'module-Fmt' '--child' 'module-Fmt_cli' '--child' 'module-Fmt_tty' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/stdlib.mld' '-I' '.' '-o' './page-stdlib.odoc' '--child' 'module-CamlinternalFormat' '--child' 'module-CamlinternalFormatBasics' '--child' 'module-CamlinternalLazy' '--child' 'module-CamlinternalMod' '--child' 'module-CamlinternalOO' '--child' 'module-CSE' '--child' 'module-CSEgen' '--child' 'module-Afl_instrument' '--child' 'module-Alias_analysis' '--child' 'module-Allocated_const' '--child' 'module-Annot' '--child' 'module-Arch' '--child' 'module-Arg_helper' '--child' 'module-Asmgen' '--child' 'module-Asmlibrarian' '--child' 'module-Asmlink' '--child' 'module-Asmpackager' '--child' 'module-Ast_helper' '--child' 'module-Ast_invariants' '--child' 'module-Ast_iterator' '--child' 'module-Ast_mapper' '--child' 'module-Asttypes' '--child' 'module-Attr_helper' '--child' 'module-Augment_specialised_args' '--child' 'module-Backend_intf' '--child' 'module-Backend_var' '--child' 'module-Binutils' '--child' 'module-Branch_relaxation' '--child' 'module-Branch_relaxation_intf' '--child' 'module-Btype' '--child' 'module-Build_export_info' '--child' 'module-Build_path_prefix_map' '--child' 'module-Builtin_attributes' '--child' 'module-Bytegen' '--child' 'module-Bytelibrarian' '--child' 'module-Bytelink' '--child' 'module-Bytepackager' '--child' 'module-Bytesections' '--child' 'module-CamlinternalMenhirLib' '--child' 'module-Ccomp' '--child' 'module-Clambda' '--child' 'module-Clambda_primitives' '--child' 'module-Clflags' '--child' 'module-Closure' '--child' 'module-Closure_conversion' '--child' 'module-Closure_conversion_aux' '--child' 'module-Closure_element' '--child' 'module-Closure_id' '--child' 'module-Closure_middle_end' '--child' 'module-Closure_offsets' '--child' 'module-Closure_origin' '--child' 'module-Cmi_format' '--child' 'module-Cmm' '--child' 'module-Cmm_helpers' '--child' 'module-Cmm_invariants' '--child' 'module-Cmmgen' '--child' 'module-Cmmgen_state' '--child' 'module-Cmo_format' '--child' 'module-Cmt2annot' '--child' 'module-Cmt_format' '--child' 'module-Cmx_format' '--child' 'module-Cmxs_format' '--child' 'module-Coloring' '--child' 'module-Comballoc' '--child' 'module-Compenv' '--child' 'module-Compilation_unit' '--child' 'module-Compile' '--child' 'module-Compile_common' '--child' 'module-Compilenv' '--child' 'module-Compmisc' '--child' 'module-Config' '--child' 'module-Config_boot' '--child' 'module-Config_main' '--child' 'module-Consistbl' '--child' 'module-Convert_primitives' '--child' 'module-Ctype' '--child' 'module-Dataflow' '--child' 'module-Datarepr' '--child' 'module-Deadcode' '--child' 'module-Debuginfo' '--child' 'module-Depend' '--child' 'module-Diffing' '--child' 'module-Diffing_with_keys' '--child' 'module-Dll' '--child' 'module-Docstrings' '--child' 'module-Domainstate' '--child' 'module-Effect_analysis' '--child' 'module-Emit' '--child' 'module-Emitaux' '--child' 'module-Emitcode' '--child' 'module-Emitenv' '--child' 'module-Env' '--child' 'module-Envaux' '--child' 'module-Errors' '--child' 'module-Errortrace' '--child' 'module-Export_id' '--child' 'module-Export_info' '--child' 'module-Export_info_for_pack' '--child' 'module-Expunge' '--child' 'module-Extract_projections' '--child' 'module-Find_recursive_functions' '--child' 'module-Flambda' '--child' 'module-Flambda_invariants' '--child' 'module-Flambda_iterators' '--child' 'module-Flambda_middle_end' '--child' 'module-Flambda_to_clambda' '--child' 'module-Flambda_utils' '--child' 'module-Freshening' '--child' 'module-Genprintval' '--child' 'module-Id_types' '--child' 'module-Ident' '--child' 'module-Identifiable' '--child' 'module-Import_approx' '--child' 'module-Includeclass' '--child' 'module-Includecore' '--child' 'module-Includemod' '--child' 'module-Includemod_errorprinter' '--child' 'module-Inconstant_idents' '--child' 'module-Initialize_symbol_to_let_symbol' '--child' 'module-Inline_and_simplify' '--child' 'module-Inline_and_simplify_aux' '--child' 'module-Inlining_cost' '--child' 'module-Inlining_decision' '--child' 'module-Inlining_decision_intf' '--child' 'module-Inlining_stats' '--child' 'module-Inlining_stats_types' '--child' 'module-Inlining_transforms' '--child' 'module-Instruct' '--child' 'module-Int_replace_polymorphic_compare' '--child' 'module-Interf' '--child' 'module-Internal_variable_names' '--child' 'module-Interval' '--child' 'module-Invariant_params' '--child' 'module-Lambda' '--child' 'module-Lazy_backtrack' '--child' 'module-Lexer' '--child' 'module-Lift_code' '--child' 'module-Lift_constants' '--child' 'module-Lift_let_to_initialize_symbol' '--child' 'module-Linear' '--child' 'module-Linear_format' '--child' 'module-Linearize' '--child' 'module-Linkage_name' '--child' 'module-Linscan' '--child' 'module-Liveness' '--child' 'module-Load_path' '--child' 'module-Local_store' '--child' 'module-Location' '--child' 'module-Longident' '--child' 'module-Mach' '--child' 'module-Main' '--child' 'module-Main_args' '--child' 'module-Maindriver' '--child' 'module-Makedepend' '--child' 'module-Matching' '--child' 'module-Meta' '--child' 'module-Misc' '--child' 'module-Mtype' '--child' 'module-Mutable_variable' '--child' 'module-Numbers' '--child' 'module-Opcodes' '--child' 'module-Oprint' '--child' 'module-Optcompile' '--child' 'module-Opterrors' '--child' 'module-Optmain' '--child' 'module-Optmaindriver' '--child' 'module-Outcometree' '--child' 'module-Parameter' '--child' 'module-Parmatch' '--child' 'module-Parse' '--child' 'module-Parser' '--child' 'module-Parsetree' '--child' 'module-Pass_wrapper' '--child' 'module-Path' '--child' 'module-Patterns' '--child' 'module-Persistent_env' '--child' 'module-Polling' '--child' 'module-Pparse' '--child' 'module-Pprintast' '--child' 'module-Predef' '--child' 'module-Primitive' '--child' 'module-Printast' '--child' 'module-Printclambda' '--child' 'module-Printclambda_primitives' '--child' 'module-Printcmm' '--child' 'module-Printinstr' '--child' 'module-Printlambda' '--child' 'module-Printlinear' '--child' 'module-Printmach' '--child' 'module-Printpat' '--child' 'module-Printtyp' '--child' 'module-Printtyped' '--child' 'module-Proc' '--child' 'module-Profile' '--child' 'module-Projection' '--child' 'module-Rec_check' '--child' 'module-Ref_to_variables' '--child' 'module-Reg' '--child' 'module-Reload' '--child' 'module-Reloadgen' '--child' 'module-Remove_free_vars_equal_to_args' '--child' 'module-Remove_unused_arguments' '--child' 'module-Remove_unused_closure_vars' '--child' 'module-Remove_unused_program_constructs' '--child' 'module-Runtimedef' '--child' 'module-Schedgen' '--child' 'module-Scheduling' '--child' 'module-Selectgen' '--child' 'module-Selection' '--child' 'module-Semantics_of_primitives' '--child' 'module-Set_of_closures_id' '--child' 'module-Set_of_closures_origin' '--child' 'module-Shape' '--child' 'module-Share_constants' '--child' 'module-Signature_group' '--child' 'module-Simple_value_approx' '--child' 'module-Simplif' '--child' 'module-Simplify_boxed_integer_ops' '--child' 'module-Simplify_boxed_integer_ops_intf' '--child' 'module-Simplify_common' '--child' 'module-Simplify_primitives' '--child' 'module-Spill' '--child' 'module-Split' '--child' 'module-Static_exception' '--child' 'module-Strmatch' '--child' 'module-Strongly_connected_components' '--child' 'module-Stypes' '--child' 'module-Subst' '--child' 'module-Switch' '--child' 'module-Symbol' '--child' 'module-Symtable' '--child' 'module-Syntaxerr' '--child' 'module-Tag' '--child' 'module-Targetint' '--child' 'module-Tast_iterator' '--child' 'module-Tast_mapper' '--child' 'module-Terminfo' '--child' 'module-Tmc' '--child' 'module-Topcommon' '--child' 'module-Topdirs' '--child' 'module-Topeval' '--child' 'module-Tophooks' '--child' 'module-Toploop' '--child' 'module-Topmain' '--child' 'module-Topstart' '--child' 'module-Trace' '--child' 'module-Translattribute' '--child' 'module-Translclass' '--child' 'module-Translcore' '--child' 'module-Translmod' '--child' 'module-Translobj' '--child' 'module-Translprim' '--child' 'module-Traverse_for_exported_symbols' '--child' 'module-Type_immediacy' '--child' 'module-Typeclass' '--child' 'module-Typecore' '--child' 'module-Typedecl' '--child' 'module-Typedecl_immediacy' '--child' 'module-Typedecl_properties' '--child' 'module-Typedecl_separability' '--child' 'module-Typedecl_unboxed' '--child' 'module-Typedecl_variance' '--child' 'module-Typedtree' '--child' 'module-Typemod' '--child' 'module-Typeopt' '--child' 'module-Types' '--child' 'module-Typetexp' '--child' 'module-Un_anf' '--child' 'module-Unbox_closures' '--child' 'module-Unbox_free_vars_of_closures' '--child' 'module-Unbox_specialised_args' '--child' 'module-Untypeast' '--child' 'module-Var_within_closure' '--child' 'module-Variable' '--child' 'module-Warnings' '--child' 'module-X86_ast' '--child' 'module-X86_dsl' '--child' 'module-X86_gas' '--child' 'module-X86_masm' '--child' 'module-X86_proc' '--child' 'module-Dynlink' '--child' 'module-Ocamlmktop_init' '--child' 'module-Profiling' '--child' 'module-Runtime_events' '--child' 'module-Std_exit' '--child' 'module-Stdlib' '--child' 'module-Stdlib__Arg' '--child' 'module-Stdlib__Array' '--child' 'module-Stdlib__ArrayLabels' '--child' 'module-Stdlib__Atomic' '--child' 'module-Stdlib__Bigarray' '--child' 'module-Stdlib__Bool' '--child' 'module-Stdlib__Buffer' '--child' 'module-Stdlib__Bytes' '--child' 'module-Stdlib__BytesLabels' '--child' 'module-Stdlib__Callback' '--child' 'module-Stdlib__Char' '--child' 'module-Stdlib__Complex' '--child' 'module-Stdlib__Condition' '--child' 'module-Stdlib__Digest' '--child' 'module-Stdlib__Domain' '--child' 'module-Stdlib__Effect' '--child' 'module-Stdlib__Either' '--child' 'module-Stdlib__Ephemeron' '--child' 'module-Stdlib__Filename' '--child' 'module-Stdlib__Float' '--child' 'module-Stdlib__Format' '--child' 'module-Stdlib__Fun' '--child' 'module-Stdlib__Gc' '--child' 'module-Stdlib__Hashtbl' '--child' 'module-Stdlib__In_channel' '--child' 'module-Stdlib__Int' '--child' 'module-Stdlib__Int32' '--child' 'module-Stdlib__Int64' '--child' 'module-Stdlib__Lazy' '--child' 'module-Stdlib__Lexing' '--child' 'module-Stdlib__List' '--child' 'module-Stdlib__ListLabels' '--child' 'module-Stdlib__Map' '--child' 'module-Stdlib__Marshal' '--child' 'module-Stdlib__MoreLabels' '--child' 'module-Stdlib__Mutex' '--child' 'module-Stdlib__Nativeint' '--child' 'module-Stdlib__Obj' '--child' 'module-Stdlib__Oo' '--child' 'module-Stdlib__Option' '--child' 'module-Stdlib__Out_channel' '--child' 'module-Stdlib__Parsing' '--child' 'module-Stdlib__Printexc' '--child' 'module-Stdlib__Printf' '--child' 'module-Stdlib__Queue' '--child' 'module-Stdlib__Random' '--child' 'module-Stdlib__Result' '--child' 'module-Stdlib__Scanf' '--child' 'module-Stdlib__Semaphore' '--child' 'module-Stdlib__Seq' '--child' 'module-Stdlib__Set' '--child' 'module-Stdlib__Stack' '--child' 'module-Stdlib__StdLabels' '--child' 'module-Stdlib__String' '--child' 'module-Stdlib__StringLabels' '--child' 'module-Stdlib__Sys' '--child' 'module-Stdlib__Uchar' '--child' 'module-Stdlib__Unit' '--child' 'module-Stdlib__Weak' '--child' 'module-Str' '--child' 'module-Event' '--child' 'module-Thread' '--child' 'module-Unix' '--child' 'module-UnixLabels' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/yojson.mld' '-I' '.' '-o' './page-yojson.odoc' '--child' 'module-Yojson' '--child' 'module-Yojson_biniou' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/biniou.mld' '-I' '.' '-o' './page-biniou.odoc' '--child' 'module-Bi_dump' '--child' 'module-Bi_inbuf' '--child' 'module-Bi_io' '--child' 'module-Bi_outbuf' '--child' 'module-Bi_share' '--child' 'module-Bi_stream' '--child' 'module-Bi_util' '--child' 'module-Bi_vint' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_xref_test.mld' '-I' '.' '-o' './page-odoc_xref_test.odoc' '--child' 'module-Odoc_xref_test' '--child' 'module-Odoc_xref_test__Common' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_xref2.mld' '-I' '.' '-o' './page-odoc_xref2.odoc' '--child' 'module-Odoc_xref2' '--child' 'module-Odoc_xref2__Cfrag' '--child' 'module-Odoc_xref2__Compile' '--child' 'module-Odoc_xref2__Component' '--child' 'module-Odoc_xref2__Cpath' '--child' 'module-Odoc_xref2__Env' '--child' 'module-Odoc_xref2__Errors' '--child' 'module-Odoc_xref2__Expand_tools' '--child' 'module-Odoc_xref2__Find' '--child' 'module-Odoc_xref2__Ident' '--child' 'module-Odoc_xref2__Lang_of' '--child' 'module-Odoc_xref2__Link' '--child' 'module-Odoc_xref2__Lookup_failures' '--child' 'module-Odoc_xref2__Ref_tools' '--child' 'module-Odoc_xref2__Strengthen' '--child' 'module-Odoc_xref2__Subst' '--child' 'module-Odoc_xref2__Tools' '--child' 'module-Odoc_xref2__Type_of' '--child' 'module-Odoc_xref2__Utils' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_odoc.mld' '-I' '.' '-o' './page-odoc_odoc.odoc' '--child' 'module-Odoc_odoc' '--child' 'module-Odoc_odoc__Compile' '--child' 'module-Odoc_odoc__Depends' '--child' 'module-Odoc_odoc__Fs' '--child' 'module-Odoc_odoc__Html_fragment' '--child' 'module-Odoc_odoc__Html_page' '--child' 'module-Odoc_odoc__Latex' '--child' 'module-Odoc_odoc__Man_page' '--child' 'module-Odoc_odoc__Odoc_file' '--child' 'module-Odoc_odoc__Odoc_link' '--child' 'module-Odoc_odoc__Or_error' '--child' 'module-Odoc_odoc__Rendering' '--child' 'module-Odoc_odoc__Resolver' '--child' 'module-Odoc_odoc__Source_tree' '--child' 'module-Odoc_odoc__Support_files' '--child' 'module-Odoc_odoc__Url' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_html_support_files.mld' '-I' '.' '-o' './page-odoc_html_support_files.odoc' '--child' 'module-Odoc_html_support_files' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_model_desc.mld' '-I' '.' '-o' './page-odoc_model_desc.odoc' '--child' 'module-Odoc_model_desc' '--child' 'module-Odoc_model_desc__Comment_desc' '--child' 'module-Odoc_model_desc__Lang_desc' '--child' 'module-Odoc_model_desc__Paths_desc' '--child' 'module-Odoc_model_desc__Type_desc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_model.mld' '-I' '.' '-o' './page-odoc_model.odoc' '--child' 'module-Odoc_model' '--child' 'module-Odoc_model__' '--child' 'module-Odoc_model__Comment' '--child' 'module-Odoc_model__Compat' '--child' 'module-Odoc_model__Error' '--child' 'module-Odoc_model__Lang' '--child' 'module-Odoc_model__Location_' '--child' 'module-Odoc_model__Names' '--child' 'module-Odoc_model__Paths' '--child' 'module-Odoc_model__Paths_types' '--child' 'module-Odoc_model__Predefined' '--child' 'module-Odoc_model__Reference' '--child' 'module-Odoc_model__Root' '--child' 'module-Odoc_model__Semantics' '--child' 'module-Odoc_model_desc' '--child' 'module-Odoc_model_desc__Comment_desc' '--child' 'module-Odoc_model_desc__Lang_desc' '--child' 'module-Odoc_model_desc__Paths_desc' '--child' 'module-Odoc_model_desc__Type_desc' '--child' 'module-Odoc_model_semantics_test' '--child' 'module-Odoc_model_semantics_test__Test' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_manpage.mld' '-I' '.' '-o' './page-odoc_manpage.odoc' '--child' 'module-Odoc_manpage' '--child' 'module-Odoc_manpage__Generator' '--child' 'module-Odoc_manpage__Link' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_loader.mld' '-I' '.' '-o' './page-odoc_loader.odoc' '--child' 'module-Odoc_loader' '--child' 'module-Odoc_loader__' '--child' 'module-Odoc_loader__Cmi' '--child' 'module-Odoc_loader__Cmt' '--child' 'module-Odoc_loader__Cmti' '--child' 'module-Odoc_loader__Doc_attr' '--child' 'module-Odoc_loader__Ident_env' '--child' 'module-Odoc_loader__Local_jmp' '--child' 'module-Odoc_loader__Lookup_def' '--child' 'module-Odoc_loader__Source_info' '--child' 'module-Odoc_loader__Uid' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_latex.mld' '-I' '.' '-o' './page-odoc_latex.odoc' '--child' 'module-Odoc_latex' '--child' 'module-Odoc_latex__Generator' '--child' 'module-Odoc_latex__Raw' '--child' 'module-Odoc_latex__Types' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_html.mld' '-I' '.' '-o' './page-odoc_html.odoc' '--child' 'module-Odoc_html' '--child' 'module-Odoc_html__' '--child' 'module-Odoc_html__Config' '--child' 'module-Odoc_html__Generator' '--child' 'module-Odoc_html__Html_fragment_json' '--child' 'module-Odoc_html__Html_page' '--child' 'module-Odoc_html__Html_source' '--child' 'module-Odoc_html__Link' '--child' 'module-Odoc_html__Types' '--child' 'module-Odoc_html__Utils' '--child' 'module-Odoc_html_support_files' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_document.mld' '-I' '.' '-o' './page-odoc_document.odoc' '--child' 'module-Odoc_document' '--child' 'module-Odoc_document__Codefmt' '--child' 'module-Odoc_document__Comment' '--child' 'module-Odoc_document__Compat' '--child' 'module-Odoc_document__Doctree' '--child' 'module-Odoc_document__Generator' '--child' 'module-Odoc_document__Generator_signatures' '--child' 'module-Odoc_document__ML' '--child' 'module-Odoc_document__Reason' '--child' 'module-Odoc_document__Renderer' '--child' 'module-Odoc_document__Targets' '--child' 'module-Odoc_document__Types' '--child' 'module-Odoc_document__Url' '--child' 'module-Odoc_document__Utils' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_examples.mld' '-I' '.' '-o' './page-odoc_examples.odoc' '--child' 'module-Odoc_examples' '--child' 'module-Odoc_examples__' '--child' 'module-Odoc_examples__Expansion' '--child' 'module-Odoc_examples__Markup' '--child' 'module-Odoc_examples__Resolution' '--child' 'module-Odoc_examples__Unexposed' '--child' 'module-Odoc_examples__Wrapping' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'source-tree' '-I' '.' '--parent' 'page-"odoc"' '-o' 'src-source.odoc' 'source.map' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../test/xref2/lib/.odoc_xref_test.objs/byte/odoc_xref_test__Common.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/warnings.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalFormatBasics.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalFormatBasics.cmti' '-I' '.' '-o' './camlinternalFormatBasics.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalLazy.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib.cmti' '-I' '.' '-o' './stdlib.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalLazy.cmti' '-I' '.' '-o' './camlinternalLazy.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Lazy.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Lazy.cmti' '-I' '.' '-o' './stdlib__Lazy.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Lexing.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Lexing.cmti' '-I' '.' '-o' './stdlib__Lexing.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Sys.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Sys.cmti' '-I' '.' '-o' './stdlib__Sys.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/warnings.cmti' '-I' '.' '-o' './warnings.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/types.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asttypes.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/location.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Buffer.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Either.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Either.cmti' '-I' '.' '-o' './stdlib__Either.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Seq.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Seq.cmti' '-I' '.' '-o' './stdlib__Seq.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Uchar.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Uchar.cmti' '-I' '.' '-o' './stdlib__Uchar.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Buffer.cmti' '-I' '.' '-o' './stdlib__Buffer.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Domain.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Domain.cmti' '-I' '.' '-o' './stdlib__Domain.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Format.cmti' '-I' '.' '-o' './stdlib__Format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/location.cmti' '-I' '.' '-o' './location.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asttypes.cmti' '-I' '.' '-o' './asttypes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ident.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/identifiable.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Hashtbl.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Hashtbl.cmti' '-I' '.' '-o' './stdlib__Hashtbl.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Map.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Map.cmti' '-I' '.' '-o' './stdlib__Map.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Set.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Set.cmti' '-I' '.' '-o' './stdlib__Set.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/identifiable.cmti' '-I' '.' '-o' './identifiable.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ident.cmti' '-I' '.' '-o' './ident.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/longident.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/longident.cmti' '-I' '.' '-o' './longident.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/outcometree.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parsetree.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parsetree.cmti' '-I' '.' '-o' './parsetree.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/type_immediacy.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/type_immediacy.cmti' '-I' '.' '-o' './type_immediacy.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/outcometree.cmti' '-I' '.' '-o' './outcometree.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/path.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/path.cmti' '-I' '.' '-o' './path.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/primitive.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/primitive.cmti' '-I' '.' '-o' './primitive.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/shape.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/shape.cmti' '-I' '.' '-o' './shape.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/types.cmti' '-I' '.' '-o' './types.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typemod.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/btype.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/btype.cmti' '-I' '.' '-o' './btype.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/build_path_prefix_map.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/build_path_prefix_map.cmti' '-I' '.' '-o' './build_path_prefix_map.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmi_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/misc.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Digest.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Digest.cmti' '-I' '.' '-o' './stdlib__Digest.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__String.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__String.cmti' '-I' '.' '-o' './stdlib__String.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/misc.cmti' '-I' '.' '-o' './misc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmi_format.cmti' '-I' '.' '-o' './cmi_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ctype.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/env.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/load_path.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/load_path.cmti' '-I' '.' '-o' './load_path.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/subst.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/subst.cmti' '-I' '.' '-o' './subst.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/env.cmti' '-I' '.' '-o' './env.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/errortrace.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/errortrace.cmti' '-I' '.' '-o' './errortrace.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ctype.cmti' '-I' '.' '-o' './ctype.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/diffing.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/diffing.cmti' '-I' '.' '-o' './diffing.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/diffing_with_keys.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/diffing_with_keys.cmti' '-I' '.' '-o' './diffing_with_keys.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/includecore.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedtree.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedtree.cmti' '-I' '.' '-o' './typedtree.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/includecore.cmti' '-I' '.' '-o' './includecore.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/includemod.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/includemod.cmti' '-I' '.' '-o' './includemod.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_immediacy.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_properties.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_properties.cmti' '-I' '.' '-o' './typedecl_properties.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_immediacy.cmti' '-I' '.' '-o' './typedecl_immediacy.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_separability.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_separability.cmti' '-I' '.' '-o' './typedecl_separability.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_variance.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_variance.cmti' '-I' '.' '-o' './typedecl_variance.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl.cmti' '-I' '.' '-o' './typedecl.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typemod.cmti' '-I' '.' '-o' './typemod.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/toploop.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Int32.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Int32.cmti' '-I' '.' '-o' './stdlib__Int32.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Obj.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Obj.cmti' '-I' '.' '-o' './stdlib__Obj.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/toploop.cmti' '-I' '.' '-o' './toploop.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Result.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Result.cmti' '-I' '.' '-o' './stdlib__Result.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Printf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Printf.cmti' '-I' '.' '-o' './stdlib__Printf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__List.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__List.cmti' '-I' '.' '-o' './stdlib__List.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Array.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Array.cmti' '-I' '.' '-o' './stdlib__Array.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Arg.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Arg.cmti' '-I' '.' '-o' './stdlib__Arg.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/result/result.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/result/result.cmt' '-I' '.' '-o' './result.odoc' '--parent' 'page-"result"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/profile.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/profile.cmti' '-I' '.' '-o' './profile.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parse.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parse.cmti' '-I' '.' '-o' './parse.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../test/xref2/lib/.odoc_xref_test.objs/byte/odoc_xref_test.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../test/xref2/lib/.odoc_xref_test.objs/byte/odoc_xref_test.cmt' '-I' '.' '-o' './odoc_xref_test.odoc' '--parent' 'page-"odoc_xref_test"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Tools.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/astring/astring.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/astring/astring.cmti' '-I' '.' '-o' './astring.odoc' '--parent' 'page-"astring"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__.cmt' '-I' '.' '-o' './odoc_model__.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model.cmt' '--source-name' 'src/model/odoc_model.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Comment.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Warning.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Loc.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__.cmt' '-I' '.' '-o' './odoc_parser__.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Loc.cmti' '-I' '.' '-o' './odoc_parser__Loc.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Warning.cmt' '-I' '.' '-o' './odoc_parser__Warning.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Ast.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Ast.cmt' '-I' '.' '-o' './odoc_parser__Ast.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser.cmti' '-I' '.' '-o' './odoc_parser.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Paths_types.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Names.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Names.cmti' '--source-name' 'src/model/names.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Names.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Paths_types.cmt' '--source-name' 'src/model/paths_types.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Paths_types.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Paths.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Paths.cmti' '--source-name' 'src/model/paths.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Paths.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Location_.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Location_.cmti' '--source-name' 'src/model/location_.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Location_.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Comment.cmt' '--source-name' 'src/model/comment.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Comment.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Error.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Error.cmti' '--source-name' 'src/model/error.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Error.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Lang.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Root.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Root.cmti' '--source-name' 'src/model/root.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Root.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Lang.cmt' '--source-name' 'src/model/lang.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Lang.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2.cmt' '-I' '.' '-o' './odoc_xref2.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Cfrag.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Ident.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Ident.cmt' '--source-name' 'src/xref2/ident.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Ident.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Cpath.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Cpath.cmt' '--source-name' 'src/xref2/cpath.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Cpath.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Cfrag.cmt' '--source-name' 'src/xref2/cfrag.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Cfrag.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Component.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Component.cmti' '--source-name' 'src/xref2/component.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Component.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Env.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Env.cmti' '--source-name' 'src/xref2/env.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Env.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Errors.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Lookup_failures.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Lookup_failures.cmti' '--source-name' 'src/xref2/lookup_failures.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Lookup_failures.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Errors.cmt' '--source-name' 'src/xref2/errors.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Errors.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Find.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Find.cmti' '--source-name' 'src/xref2/find.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Find.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Tools.cmti' '--source-name' 'src/xref2/tools.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Tools.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Compile.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Compile.cmti' '--source-name' 'src/xref2/compile.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Compile.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Resolver.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmt_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmt_format.cmti' '-I' '.' '-o' './cmt_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/fpath/fpath.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/fpath/fpath.cmti' '-I' '.' '-o' './fpath.odoc' '--parent' 'page-"fpath"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__.cmt' '-I' '.' '-o' './odoc_loader__.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Lookup_def.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Lookup_def.cmti' '--source-name' 'src/loader/lookup_def.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Lookup_def.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Source_info.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Source_info.cmti' '--source-name' 'src/loader/source_info.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Source_info.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader.cmti' '--source-name' 'src/loader/odoc_loader.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc.cmt' '-I' '.' '-o' './odoc_odoc.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Fs.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Or_error.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Or_error.cmti' '--source-name' 'src/odoc/or_error.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Or_error.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Fs.cmti' '--source-name' 'src/odoc/fs.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Fs.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Resolver.cmti' '--source-name' 'src/odoc/resolver.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Resolver.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Compat.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Compat.cmt' '--source-name' 'src/model/compat.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Compat.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Ident_env.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Ident_env.cmti' '--source-name' 'src/loader/ident_env.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Ident_env.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmti.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmti.cmti' '--source-name' 'src/loader/cmti.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Cmti.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmt.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmt.cmti' '--source-name' 'src/loader/cmt.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Cmt.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compmisc.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/clflags.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/clflags.cmti' '-I' '.' '-o' './clflags.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compmisc.cmti' '-I' '.' '-o' './compmisc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../test/xref2/lib/.odoc_xref_test.objs/byte/odoc_xref_test__Common.cmt' '-I' '.' '-o' './odoc_xref_test__Common.odoc' '--parent' 'page-"odoc_xref_test"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Utils.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Utils.cmt' '--source-name' 'src/xref2/utils.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Utils.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Type_of.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Type_of.cmti' '--source-name' 'src/xref2/type_of.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Type_of.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Subst.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Subst.cmti' '--source-name' 'src/xref2/subst.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Subst.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Strengthen.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Strengthen.cmt' '--source-name' 'src/xref2/strengthen.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Strengthen.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Ref_tools.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Ref_tools.cmti' '--source-name' 'src/xref2/ref_tools.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Ref_tools.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Link.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Link.cmti' '--source-name' 'src/xref2/link.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Link.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Lang_of.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Lang_of.cmti' '--source-name' 'src/xref2/lang_of.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Lang_of.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Expand_tools.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Expand_tools.cmt' '--source-name' 'src/xref2/expand_tools.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Expand_tools.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Url.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_wrap.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_wrap.cmti' '-I' '.' '-o' './xml_wrap.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_stream.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_sigs.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_sigs.cmti' '-I' '.' '-o' './xml_sigs.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_stream.cmti' '-I' '.' '-o' './xml_stream.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/tyxml_xml.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/tyxml_xml.cmti' '-I' '.' '-o' './tyxml_xml.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/tyxml_svg.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/svg_sigs.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/svg_types.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/svg_types.cmti' '-I' '.' '-o' './svg_types.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/svg_sigs.cmti' '-I' '.' '-o' './svg_sigs.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/tyxml_svg.cmti' '-I' '.' '-o' './tyxml_svg.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/tyxml_html.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/html_sigs.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/html_types.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/html_types.cmti' '-I' '.' '-o' './html_types.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/html_sigs.cmti' '-I' '.' '-o' './html_sigs.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/tyxml_html.cmti' '-I' '.' '-o' './tyxml_html.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/tyxml.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/tyxml.cmt' '-I' '.' '-o' './tyxml.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Html_page.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document.cmt' '-I' '.' '-o' './odoc_document.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__ML.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Types.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Url.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Url.cmti' '--source-name' 'src/document/url.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Url.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Types.cmt' '--source-name' 'src/document/types.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Types.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__ML.cmti' '--source-name' 'src/document/ML.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__ML.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Reason.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Reason.cmti' '--source-name' 'src/document/reason.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Reason.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Renderer.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Renderer.cmt' '--source-name' 'src/document/renderer.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Renderer.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__.cmt' '-I' '.' '-o' './odoc_html__.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html.cmt' '--source-name' 'src/html/odoc_html.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Config.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Types.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Types.cmt' '--source-name' 'src/html/types.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Types.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Config.cmti' '--source-name' 'src/html/config.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Config.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Html_page.cmti' '--source-name' 'src/odoc/html_page.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Html_page.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Semantics.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Semantics.cmti' '--source-name' 'src/model/semantics.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Semantics.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Generator.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/latex/.odoc_latex.objs/byte/odoc_latex.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/latex/.odoc_latex.objs/byte/odoc_latex.cmt' '-I' '.' '-o' './odoc_latex.odoc' '--parent' 'page-"odoc_latex"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Generator.cmti' '--source-name' 'src/latex/generator.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_latex__Generator.odoc' '--parent' 'page-"odoc_latex"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Link.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Link.cmti' '--source-name' 'src/html/link.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Link.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Url.cmt' '--source-name' 'src/odoc/url.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Url.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Support_files.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Support_files.cmti' '--source-name' 'src/odoc/support_files.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Support_files.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Source_tree.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Source_tree.cmti' '--source-name' 'src/odoc/source_tree.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Source_tree.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Rendering.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Rendering.cmti' '--source-name' 'src/odoc/rendering.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Rendering.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Odoc_link.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Odoc_file.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Odoc_file.cmti' '--source-name' 'src/odoc/odoc_file.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Odoc_file.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Odoc_link.cmt' '--source-name' 'src/odoc/odoc_link.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Odoc_link.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Man_page.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage__Generator.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage.cmt' '-I' '.' '-o' './odoc_manpage.odoc' '--parent' 'page-"odoc_manpage"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage__Generator.cmti' '--source-name' 'src/manpage/generator.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_manpage__Generator.odoc' '--parent' 'page-"odoc_manpage"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Man_page.cmt' '--source-name' 'src/odoc/man_page.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Man_page.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Latex.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Latex.cmt' '--source-name' 'src/odoc/latex.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Latex.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Html_fragment.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Html_fragment.cmti' '--source-name' 'src/odoc/html_fragment.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Html_fragment.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Depends.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Depends.cmti' '--source-name' 'src/odoc/depends.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Depends.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Compile.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Compile.cmti' '--source-name' 'src/odoc/compile.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Compile.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html_support_files/.odoc_html_support_files.objs/byte/odoc_html_support_files.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html_support_files/.odoc_html_support_files.objs/byte/odoc_html_support_files.cmt' '--source-name' 'src/html_support_files/odoc_html_support_files.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html_support_files.odoc' '--parent' 'page-"odoc_html_support_files"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Type_desc.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc.cmt' '-I' '.' '-o' './odoc_model_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Type_desc.cmt' '--source-name' 'src/model_desc/type_desc.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model_desc__Type_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Paths_desc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Paths_desc.cmti' '--source-name' 'src/model_desc/paths_desc.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model_desc__Paths_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Lang_desc.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Comment_desc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Comment_desc.cmti' '--source-name' 'src/model_desc/comment_desc.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model_desc__Comment_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Lang_desc.cmt' '--source-name' 'src/model_desc/lang_desc.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model_desc__Lang_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../test/model/semantics/.odoc_model_semantics_test.objs/byte/odoc_model_semantics_test__Test.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/yojson/yojson.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_outbuf.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_share.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_share.cmti' '-I' '.' '-o' './bi_share.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_outbuf.cmti' '-I' '.' '-o' './bi_outbuf.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/yojson/yojson.cmti' '-I' '.' '-o' './yojson.odoc' '--parent' 'page-"yojson"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__StringLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__StringLabels.cmti' '-I' '.' '-o' './stdlib__StringLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__StdLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__StdLabels.cmti' '-I' '.' '-o' './stdlib__StdLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Printexc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Printexc.cmti' '-I' '.' '-o' './stdlib__Printexc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Nativeint.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Nativeint.cmti' '-I' '.' '-o' './stdlib__Nativeint.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__MoreLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__MoreLabels.cmti' '-I' '.' '-o' './stdlib__MoreLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__ListLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__ListLabels.cmti' '-I' '.' '-o' './stdlib__ListLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Int64.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Int64.cmti' '-I' '.' '-o' './stdlib__Int64.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__BytesLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__BytesLabels.cmti' '-I' '.' '-o' './stdlib__BytesLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../test/model/semantics/.odoc_model_semantics_test.objs/byte/odoc_model_semantics_test.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../test/model/semantics/.odoc_model_semantics_test.objs/byte/odoc_model_semantics_test.cmt' '-I' '.' '-o' './odoc_model_semantics_test.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../test/model/semantics/.odoc_model_semantics_test.objs/byte/odoc_model_semantics_test__Test.cmt' '-I' '.' '-o' './odoc_model_semantics_test__Test.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Reference.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Reference.cmti' '--source-name' 'src/model/reference.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Reference.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Predefined.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Predefined.cmti' '--source-name' 'src/model/predefined.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Predefined.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage__Link.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage__Link.cmt' '--source-name' 'src/manpage/link.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_manpage__Link.odoc' '--parent' 'page-"odoc_manpage"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Uid.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Uid.cmti' '--source-name' 'src/loader/uid.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Uid.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Local_jmp.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Local_jmp.cmti' '--source-name' 'src/loader/local_jmp.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Local_jmp.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Doc_attr.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Doc_attr.cmti' '--source-name' 'src/loader/doc_attr.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Doc_attr.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmi.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmi.cmti' '--source-name' 'src/loader/cmi.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Cmi.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Types.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Types.cmt' '--source-name' 'src/latex/types.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_latex__Types.odoc' '--parent' 'page-"odoc_latex"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Raw.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/fmt/fmt.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Queue.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Queue.cmti' '-I' '.' '-o' './stdlib__Queue.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Stack.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Stack.cmti' '-I' '.' '-o' './stdlib__Stack.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/fmt/fmt.cmti' '-I' '.' '-o' './fmt.odoc' '--parent' 'page-"fmt"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Raw.cmti' '--source-name' 'src/latex/raw.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_latex__Raw.odoc' '--parent' 'page-"odoc_latex"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Utils.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Char.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Char.cmti' '-I' '.' '-o' './stdlib__Char.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Utils.cmt' '--source-name' 'src/html/utils.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Utils.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Html_source.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Html_source.cmti' '--source-name' 'src/html/html_source.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Html_source.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Html_page.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Html_page.cmti' '--source-name' 'src/html/html_page.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Html_page.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Html_fragment_json.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Html_fragment_json.cmti' '--source-name' 'src/html/html_fragment_json.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Html_fragment_json.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Generator.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Generator.cmti' '--source-name' 'src/html/generator.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Generator.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Utils.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Utils.cmti' '--source-name' 'src/document/utils.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Utils.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Targets.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Targets.cmti' '--source-name' 'src/document/targets.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Targets.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Generator_signatures.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Codefmt.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Codefmt.cmti' '--source-name' 'src/document/codefmt.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Codefmt.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Generator_signatures.cmt' '--source-name' 'src/document/generator_signatures.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Generator_signatures.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Generator.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Generator.cmti' '--source-name' 'src/document/generator.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Generator.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Doctree.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Doctree.cmt' '--source-name' 'src/document/doctree.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Doctree.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Compat.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Compat.cmt' '--source-name' 'src/document/compat.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Compat.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Comment.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Comment.cmt' '--source-name' 'src/document/comment.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Comment.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Wrapping.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__.cmt' '-I' '.' '-o' './odoc_examples__.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Unexposed.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Unexposed.cmti' '-I' '.' '-o' './odoc_examples__Unexposed.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Wrapping.cmti' '-I' '.' '-o' './odoc_examples__Wrapping.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Resolution.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Resolution.cmti' '-I' '.' '-o' './odoc_examples__Resolution.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Markup.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Markup.cmti' '-I' '.' '-o' './odoc_examples__Markup.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Expansion.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Expansion.cmti' '-I' '.' '-o' './odoc_examples__Expansion.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples.cmt' '-I' '.' '-o' './odoc_examples.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Token.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Token.cmt' '-I' '.' '-o' './odoc_parser__Token.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Syntax.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Syntax.cmti' '-I' '.' '-o' './odoc_parser__Syntax.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Parse_error.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Parse_error.cmt' '-I' '.' '-o' './odoc_parser__Parse_error.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Lexer.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Lexer.cmti' '-I' '.' '-o' './odoc_parser__Lexer.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/cmdliner/cmdliner.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/cmdliner/cmdliner.cmti' '-I' '.' '-o' './cmdliner.odoc' '--parent' 'page-"cmdliner"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_print.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_print.cmti' '-I' '.' '-o' './xml_print.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_iter.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_iter.cmti' '-I' '.' '-o' './xml_iter.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/svg_f.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/svg_f.cmti' '-I' '.' '-o' './svg_f.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/html_f.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/html_f.cmti' '-I' '.' '-o' './html_f.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/fmt/fmt_tty.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/fmt/fmt_tty.cmti' '-I' '.' '-o' './fmt_tty.odoc' '--parent' 'page-"fmt"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/fmt/fmt_cli.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/fmt/fmt_cli.cmti' '-I' '.' '-o' './fmt_cli.odoc' '--parent' 'page-"fmt"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/unix/unixLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Bigarray.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Complex.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Complex.cmti' '-I' '.' '-o' './stdlib__Complex.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Bigarray.cmti' '-I' '.' '-o' './stdlib__Bigarray.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/unix/unix.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/unix/unix.cmti' '-I' '.' '-o' './unix.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/unix/unixLabels.cmti' '-I' '.' '-o' './unixLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/threads/thread.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/threads/thread.cmti' '-I' '.' '-o' './thread.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/threads/event.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/threads/event.cmti' '-I' '.' '-o' './event.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/str/str.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/str/str.cmti' '-I' '.' '-o' './str.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Weak.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Weak.cmti' '-I' '.' '-o' './stdlib__Weak.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Unit.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Unit.cmti' '-I' '.' '-o' './stdlib__Unit.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Semaphore.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Semaphore.cmti' '-I' '.' '-o' './stdlib__Semaphore.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Scanf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Scanf.cmti' '-I' '.' '-o' './stdlib__Scanf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Random.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Random.cmti' '-I' '.' '-o' './stdlib__Random.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Parsing.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Parsing.cmti' '-I' '.' '-o' './stdlib__Parsing.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Out_channel.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Out_channel.cmti' '-I' '.' '-o' './stdlib__Out_channel.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Option.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Option.cmti' '-I' '.' '-o' './stdlib__Option.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Oo.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalOO.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalOO.cmti' '-I' '.' '-o' './camlinternalOO.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Oo.cmti' '-I' '.' '-o' './stdlib__Oo.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Mutex.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Mutex.cmti' '-I' '.' '-o' './stdlib__Mutex.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Marshal.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Marshal.cmti' '-I' '.' '-o' './stdlib__Marshal.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Int.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Int.cmti' '-I' '.' '-o' './stdlib__Int.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__In_channel.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__In_channel.cmti' '-I' '.' '-o' './stdlib__In_channel.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Gc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Gc.cmti' '-I' '.' '-o' './stdlib__Gc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Fun.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Fun.cmti' '-I' '.' '-o' './stdlib__Fun.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Float.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Float.cmti' '-I' '.' '-o' './stdlib__Float.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Filename.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Filename.cmti' '-I' '.' '-o' './stdlib__Filename.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Ephemeron.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Ephemeron.cmti' '-I' '.' '-o' './stdlib__Ephemeron.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Effect.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Effect.cmti' '-I' '.' '-o' './stdlib__Effect.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Condition.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Condition.cmti' '-I' '.' '-o' './stdlib__Condition.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Callback.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Callback.cmti' '-I' '.' '-o' './stdlib__Callback.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Bytes.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Bytes.cmti' '-I' '.' '-o' './stdlib__Bytes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Bool.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Bool.cmti' '-I' '.' '-o' './stdlib__Bool.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Atomic.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Atomic.cmti' '-I' '.' '-o' './stdlib__Atomic.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__ArrayLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__ArrayLabels.cmti' '-I' '.' '-o' './stdlib__ArrayLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/std_exit.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/std_exit.cmt' '-I' '.' '-o' './std_exit.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/runtime_events/runtime_events.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/runtime_events/runtime_events.cmti' '-I' '.' '-o' './runtime_events.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/profiling/profiling.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/profiling/profiling.cmti' '-I' '.' '-o' './profiling.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/ocamlmktop/ocamlmktop_init.cmi' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/genprintval.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/genprintval.cmti' '-I' '.' '-o' './genprintval.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topcommon.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topcommon.cmti' '-I' '.' '-o' './topcommon.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/ocamlmktop/ocamlmktop_init.cmi' '-I' '.' '-o' './ocamlmktop_init.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/dynlink/dynlink.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/dynlink/dynlink.cmti' '-I' '.' '-o' './dynlink.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_proc.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_ast.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_ast.cmti' '-I' '.' '-o' './x86_ast.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_proc.cmti' '-I' '.' '-o' './x86_proc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_masm.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_masm.cmti' '-I' '.' '-o' './x86_masm.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_gas.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_gas.cmti' '-I' '.' '-o' './x86_gas.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_dsl.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_dsl.cmti' '-I' '.' '-o' './x86_dsl.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/variable.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compilation_unit.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linkage_name.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linkage_name.cmti' '-I' '.' '-o' './linkage_name.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compilation_unit.cmti' '-I' '.' '-o' './compilation_unit.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/debuginfo.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/debuginfo.cmti' '-I' '.' '-o' './debuginfo.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/internal_variable_names.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lambda.cmti' '-I' '.' '-o' './lambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/internal_variable_names.cmti' '-I' '.' '-o' './internal_variable_names.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/variable.cmti' '-I' '.' '-o' './variable.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/var_within_closure.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_element.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_element.cmti' '-I' '.' '-o' './closure_element.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/var_within_closure.cmti' '-I' '.' '-o' './var_within_closure.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/untypeast.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/untypeast.cmti' '-I' '.' '-o' './untypeast.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/unbox_specialised_args.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/allocated_const.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/allocated_const.cmti' '-I' '.' '-o' './allocated_const.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/backend_intf.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/clambda_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/clambda_primitives.cmti' '-I' '.' '-o' './clambda_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_id.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_id.cmti' '-I' '.' '-o' './closure_id.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_origin.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_origin.cmti' '-I' '.' '-o' './closure_origin.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/export_id.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/export_id.cmti' '-I' '.' '-o' './export_id.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/mutable_variable.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/mutable_variable.cmti' '-I' '.' '-o' './mutable_variable.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/numbers.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/numbers.cmti' '-I' '.' '-o' './numbers.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parameter.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parameter.cmti' '-I' '.' '-o' './parameter.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/projection.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/projection.cmti' '-I' '.' '-o' './projection.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/set_of_closures_id.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/set_of_closures_id.cmti' '-I' '.' '-o' './set_of_closures_id.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/set_of_closures_origin.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/set_of_closures_origin.cmti' '-I' '.' '-o' './set_of_closures_origin.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/static_exception.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/static_exception.cmti' '-I' '.' '-o' './static_exception.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/symbol.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/symbol.cmti' '-I' '.' '-o' './symbol.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tag.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tag.cmti' '-I' '.' '-o' './tag.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda.cmti' '-I' '.' '-o' './flambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/freshening.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/freshening.cmti' '-I' '.' '-o' './freshening.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simple_value_approx.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simple_value_approx.cmti' '-I' '.' '-o' './simple_value_approx.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/backend_intf.cmti' '-I' '.' '-o' './backend_intf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inline_and_simplify_aux.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_cost.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_cost.cmti' '-I' '.' '-o' './inlining_cost.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_stats_types.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_stats_types.cmti' '-I' '.' '-o' './inlining_stats_types.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inline_and_simplify_aux.cmti' '-I' '.' '-o' './inline_and_simplify_aux.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/unbox_specialised_args.cmti' '-I' '.' '-o' './unbox_specialised_args.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/unbox_free_vars_of_closures.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/unbox_free_vars_of_closures.cmti' '-I' '.' '-o' './unbox_free_vars_of_closures.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/unbox_closures.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/unbox_closures.cmti' '-I' '.' '-o' './unbox_closures.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/un_anf.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/backend_var.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/backend_var.cmti' '-I' '.' '-o' './backend_var.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/clambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/clambda.cmti' '-I' '.' '-o' './clambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/un_anf.cmti' '-I' '.' '-o' './un_anf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typetexp.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typetexp.cmti' '-I' '.' '-o' './typetexp.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typeopt.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typeopt.cmti' '-I' '.' '-o' './typeopt.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_unboxed.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_unboxed.cmti' '-I' '.' '-o' './typedecl_unboxed.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typecore.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typecore.cmti' '-I' '.' '-o' './typecore.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typeclass.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typeclass.cmti' '-I' '.' '-o' './typeclass.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/traverse_for_exported_symbols.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/export_info.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/export_info.cmti' '-I' '.' '-o' './export_info.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/traverse_for_exported_symbols.cmti' '-I' '.' '-o' './traverse_for_exported_symbols.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translprim.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translprim.cmti' '-I' '.' '-o' './translprim.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translobj.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translobj.cmti' '-I' '.' '-o' './translobj.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translmod.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translmod.cmti' '-I' '.' '-o' './translmod.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translcore.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translcore.cmti' '-I' '.' '-o' './translcore.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translclass.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translclass.cmti' '-I' '.' '-o' './translclass.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translattribute.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translattribute.cmti' '-I' '.' '-o' './translattribute.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/trace.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/trace.cmti' '-I' '.' '-o' './trace.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topstart.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topmain.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topmain.cmti' '-I' '.' '-o' './topmain.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topstart.cmt' '-I' '.' '-o' './topstart.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tophooks.cmi' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tophooks.cmi' '-I' '.' '-o' './tophooks.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topeval.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topeval.cmti' '-I' '.' '-o' './topeval.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topdirs.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topdirs.cmti' '-I' '.' '-o' './topdirs.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tmc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tmc.cmti' '-I' '.' '-o' './tmc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/terminfo.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/terminfo.cmti' '-I' '.' '-o' './terminfo.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tast_mapper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tast_mapper.cmti' '-I' '.' '-o' './tast_mapper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tast_iterator.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tast_iterator.cmti' '-I' '.' '-o' './tast_iterator.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/targetint.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/targetint.cmti' '-I' '.' '-o' './targetint.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/syntaxerr.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/syntaxerr.cmti' '-I' '.' '-o' './syntaxerr.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/symtable.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmo_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmo_format.cmti' '-I' '.' '-o' './cmo_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/symtable.cmti' '-I' '.' '-o' './symtable.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/switch.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/switch.cmti' '-I' '.' '-o' './switch.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/stypes.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/annot.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/annot.cmti' '-I' '.' '-o' './annot.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/stypes.cmti' '-I' '.' '-o' './stypes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/strongly_connected_components.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/strongly_connected_components.cmti' '-I' '.' '-o' './strongly_connected_components.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/strmatch.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmm.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmm.cmti' '-I' '.' '-o' './cmm.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/strmatch.cmti' '-I' '.' '-o' './strmatch.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/split.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/arch.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/config.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/config.cmti' '-I' '.' '-o' './config.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/arch.cmt' '-I' '.' '-o' './arch.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/mach.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/reg.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/reg.cmti' '-I' '.' '-o' './reg.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/mach.cmti' '-I' '.' '-o' './mach.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/split.cmti' '-I' '.' '-o' './split.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/spill.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/spill.cmti' '-I' '.' '-o' './spill.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplify_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplify_primitives.cmti' '-I' '.' '-o' './simplify_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplify_common.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplify_common.cmti' '-I' '.' '-o' './simplify_common.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplify_boxed_integer_ops_intf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplify_boxed_integer_ops_intf.cmti' '-I' '.' '-o' './simplify_boxed_integer_ops_intf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplify_boxed_integer_ops.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplify_boxed_integer_ops.cmti' '-I' '.' '-o' './simplify_boxed_integer_ops.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplif.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplif.cmti' '-I' '.' '-o' './simplif.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/signature_group.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/signature_group.cmti' '-I' '.' '-o' './signature_group.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/share_constants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/share_constants.cmti' '-I' '.' '-o' './share_constants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/semantics_of_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/semantics_of_primitives.cmti' '-I' '.' '-o' './semantics_of_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/selection.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/selection.cmti' '-I' '.' '-o' './selection.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/selectgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/selectgen.cmti' '-I' '.' '-o' './selectgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/scheduling.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linear.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linear.cmti' '-I' '.' '-o' './linear.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/scheduling.cmti' '-I' '.' '-o' './scheduling.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/schedgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/schedgen.cmti' '-I' '.' '-o' './schedgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/runtimedef.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/runtimedef.cmti' '-I' '.' '-o' './runtimedef.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_program_constructs.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_program_constructs.cmti' '-I' '.' '-o' './remove_unused_program_constructs.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_closure_vars.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_closure_vars.cmti' '-I' '.' '-o' './remove_unused_closure_vars.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_arguments.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_arguments.cmti' '-I' '.' '-o' './remove_unused_arguments.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/remove_free_vars_equal_to_args.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/remove_free_vars_equal_to_args.cmti' '-I' '.' '-o' './remove_free_vars_equal_to_args.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/reloadgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/reloadgen.cmti' '-I' '.' '-o' './reloadgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/reload.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/reload.cmti' '-I' '.' '-o' './reload.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ref_to_variables.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ref_to_variables.cmti' '-I' '.' '-o' './ref_to_variables.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/rec_check.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/rec_check.cmti' '-I' '.' '-o' './rec_check.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/proc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/proc.cmti' '-I' '.' '-o' './proc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printtyped.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printtyped.cmti' '-I' '.' '-o' './printtyped.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printtyp.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printtyp.cmti' '-I' '.' '-o' './printtyp.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printpat.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printpat.cmti' '-I' '.' '-o' './printpat.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printmach.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printmach.cmti' '-I' '.' '-o' './printmach.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printlinear.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printlinear.cmti' '-I' '.' '-o' './printlinear.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printlambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printlambda.cmti' '-I' '.' '-o' './printlambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printinstr.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/instruct.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/instruct.cmti' '-I' '.' '-o' './instruct.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printinstr.cmti' '-I' '.' '-o' './printinstr.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printcmm.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printcmm.cmti' '-I' '.' '-o' './printcmm.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printclambda_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printclambda_primitives.cmti' '-I' '.' '-o' './printclambda_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printclambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printclambda.cmti' '-I' '.' '-o' './printclambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printast.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printast.cmti' '-I' '.' '-o' './printast.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/predef.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/predef.cmti' '-I' '.' '-o' './predef.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/pprintast.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/pprintast.cmti' '-I' '.' '-o' './pprintast.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/pparse.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/pparse.cmti' '-I' '.' '-o' './pparse.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/polling.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/polling.cmti' '-I' '.' '-o' './polling.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/persistent_env.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/consistbl.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/consistbl.cmti' '-I' '.' '-o' './consistbl.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lazy_backtrack.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lazy_backtrack.cmti' '-I' '.' '-o' './lazy_backtrack.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/persistent_env.cmti' '-I' '.' '-o' './persistent_env.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/patterns.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/patterns.cmti' '-I' '.' '-o' './patterns.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/pass_wrapper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/pass_wrapper.cmti' '-I' '.' '-o' './pass_wrapper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parser.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/camlinternalMenhirLib.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/camlinternalMenhirLib.cmti' '-I' '.' '-o' './camlinternalMenhirLib.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/docstrings.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/docstrings.cmti' '-I' '.' '-o' './docstrings.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parser.cmti' '-I' '.' '-o' './parser.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parmatch.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parmatch.cmti' '-I' '.' '-o' './parmatch.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/optmaindriver.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/optmaindriver.cmti' '-I' '.' '-o' './optmaindriver.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/optmain.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/optmain.cmt' '-I' '.' '-o' './optmain.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/opterrors.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/opterrors.cmti' '-I' '.' '-o' './opterrors.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/optcompile.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compile_common.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compile_common.cmti' '-I' '.' '-o' './compile_common.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/optcompile.cmti' '-I' '.' '-o' './optcompile.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/oprint.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/oprint.cmti' '-I' '.' '-o' './oprint.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/opcodes.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/opcodes.cmti' '-I' '.' '-o' './opcodes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/mtype.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/mtype.cmti' '-I' '.' '-o' './mtype.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/meta.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/meta.cmti' '-I' '.' '-o' './meta.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/matching.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/matching.cmti' '-I' '.' '-o' './matching.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/makedepend.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/makedepend.cmti' '-I' '.' '-o' './makedepend.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/maindriver.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/maindriver.cmti' '-I' '.' '-o' './maindriver.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/main_args.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/main_args.cmti' '-I' '.' '-o' './main_args.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/main.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/main.cmt' '-I' '.' '-o' './main.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/local_store.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/local_store.cmti' '-I' '.' '-o' './local_store.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/liveness.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/liveness.cmti' '-I' '.' '-o' './liveness.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linscan.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linscan.cmti' '-I' '.' '-o' './linscan.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linearize.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linearize.cmti' '-I' '.' '-o' './linearize.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linear_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linear_format.cmti' '-I' '.' '-o' './linear_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lift_let_to_initialize_symbol.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lift_let_to_initialize_symbol.cmti' '-I' '.' '-o' './lift_let_to_initialize_symbol.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lift_constants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lift_constants.cmti' '-I' '.' '-o' './lift_constants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lift_code.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lift_code.cmti' '-I' '.' '-o' './lift_code.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lexer.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lexer.cmti' '-I' '.' '-o' './lexer.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/invariant_params.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/invariant_params.cmti' '-I' '.' '-o' './invariant_params.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/interval.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/interval.cmti' '-I' '.' '-o' './interval.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/interf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/interf.cmti' '-I' '.' '-o' './interf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/int_replace_polymorphic_compare.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/int_replace_polymorphic_compare.cmti' '-I' '.' '-o' './int_replace_polymorphic_compare.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_transforms.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_decision_intf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_decision_intf.cmti' '-I' '.' '-o' './inlining_decision_intf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_transforms.cmti' '-I' '.' '-o' './inlining_transforms.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_stats.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_stats.cmti' '-I' '.' '-o' './inlining_stats.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_decision.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_decision.cmti' '-I' '.' '-o' './inlining_decision.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inline_and_simplify.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inline_and_simplify.cmti' '-I' '.' '-o' './inline_and_simplify.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/initialize_symbol_to_let_symbol.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/initialize_symbol_to_let_symbol.cmti' '-I' '.' '-o' './initialize_symbol_to_let_symbol.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inconstant_idents.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inconstant_idents.cmti' '-I' '.' '-o' './inconstant_idents.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/includemod_errorprinter.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/includemod_errorprinter.cmti' '-I' '.' '-o' './includemod_errorprinter.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/includeclass.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/includeclass.cmti' '-I' '.' '-o' './includeclass.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/import_approx.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/import_approx.cmti' '-I' '.' '-o' './import_approx.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/id_types.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/id_types.cmti' '-I' '.' '-o' './id_types.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_utils.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_utils.cmti' '-I' '.' '-o' './flambda_utils.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_to_clambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_to_clambda.cmti' '-I' '.' '-o' './flambda_to_clambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_middle_end.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_middle_end.cmti' '-I' '.' '-o' './flambda_middle_end.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_iterators.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_iterators.cmti' '-I' '.' '-o' './flambda_iterators.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_invariants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_invariants.cmti' '-I' '.' '-o' './flambda_invariants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/find_recursive_functions.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/find_recursive_functions.cmti' '-I' '.' '-o' './find_recursive_functions.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/extract_projections.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/extract_projections.cmti' '-I' '.' '-o' './extract_projections.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/expunge.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytesections.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytesections.cmti' '-I' '.' '-o' './bytesections.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/expunge.cmt' '-I' '.' '-o' './expunge.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/export_info_for_pack.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/export_info_for_pack.cmti' '-I' '.' '-o' './export_info_for_pack.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/errors.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/errors.cmti' '-I' '.' '-o' './errors.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/envaux.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/envaux.cmti' '-I' '.' '-o' './envaux.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/emitenv.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/emitenv.cmti' '-I' '.' '-o' './emitenv.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/emitcode.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/emitcode.cmti' '-I' '.' '-o' './emitcode.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/emitaux.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/emitaux.cmti' '-I' '.' '-o' './emitaux.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/emit.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/emit.cmti' '-I' '.' '-o' './emit.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/effect_analysis.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/effect_analysis.cmti' '-I' '.' '-o' './effect_analysis.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/domainstate.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/domainstate.cmti' '-I' '.' '-o' './domainstate.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/dll.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/dll.cmti' '-I' '.' '-o' './dll.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/depend.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/depend.cmti' '-I' '.' '-o' './depend.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/deadcode.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/deadcode.cmti' '-I' '.' '-o' './deadcode.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/datarepr.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/datarepr.cmti' '-I' '.' '-o' './datarepr.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/dataflow.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/dataflow.cmti' '-I' '.' '-o' './dataflow.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/convert_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/convert_primitives.cmti' '-I' '.' '-o' './convert_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/config_main.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/config_main.cmti' '-I' '.' '-o' './config_main.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/config_boot.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/config_boot.cmti' '-I' '.' '-o' './config_boot.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compilenv.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmx_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmx_format.cmti' '-I' '.' '-o' './cmx_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compilenv.cmti' '-I' '.' '-o' './compilenv.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compile.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compile.cmti' '-I' '.' '-o' './compile.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compenv.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compenv.cmti' '-I' '.' '-o' './compenv.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/comballoc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/comballoc.cmti' '-I' '.' '-o' './comballoc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/coloring.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/coloring.cmti' '-I' '.' '-o' './coloring.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmxs_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmxs_format.cmti' '-I' '.' '-o' './cmxs_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmt2annot.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmt2annot.cmt' '-I' '.' '-o' './cmt2annot.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmmgen_state.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmmgen_state.cmti' '-I' '.' '-o' './cmmgen_state.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmmgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmmgen.cmti' '-I' '.' '-o' './cmmgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmm_invariants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmm_invariants.cmti' '-I' '.' '-o' './cmm_invariants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmm_helpers.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmm_helpers.cmti' '-I' '.' '-o' './cmm_helpers.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_offsets.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_offsets.cmti' '-I' '.' '-o' './closure_offsets.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_middle_end.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_middle_end.cmti' '-I' '.' '-o' './closure_middle_end.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_conversion_aux.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_conversion_aux.cmti' '-I' '.' '-o' './closure_conversion_aux.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_conversion.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_conversion.cmti' '-I' '.' '-o' './closure_conversion.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure.cmti' '-I' '.' '-o' './closure.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ccomp.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ccomp.cmti' '-I' '.' '-o' './ccomp.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytepackager.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytepackager.cmti' '-I' '.' '-o' './bytepackager.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytelink.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytelink.cmti' '-I' '.' '-o' './bytelink.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytelibrarian.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytelibrarian.cmti' '-I' '.' '-o' './bytelibrarian.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytegen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytegen.cmti' '-I' '.' '-o' './bytegen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/builtin_attributes.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/builtin_attributes.cmti' '-I' '.' '-o' './builtin_attributes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/build_export_info.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/build_export_info.cmti' '-I' '.' '-o' './build_export_info.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/branch_relaxation_intf.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/branch_relaxation_intf.cmt' '-I' '.' '-o' './branch_relaxation_intf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/branch_relaxation.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/branch_relaxation.cmti' '-I' '.' '-o' './branch_relaxation.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/binutils.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/binutils.cmti' '-I' '.' '-o' './binutils.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/augment_specialised_args.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/augment_specialised_args.cmti' '-I' '.' '-o' './augment_specialised_args.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/attr_helper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/attr_helper.cmti' '-I' '.' '-o' './attr_helper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ast_mapper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ast_mapper.cmti' '-I' '.' '-o' './ast_mapper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ast_iterator.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ast_iterator.cmti' '-I' '.' '-o' './ast_iterator.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ast_invariants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ast_invariants.cmti' '-I' '.' '-o' './ast_invariants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ast_helper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ast_helper.cmti' '-I' '.' '-o' './ast_helper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asmpackager.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asmpackager.cmti' '-I' '.' '-o' './asmpackager.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asmlink.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asmlink.cmti' '-I' '.' '-o' './asmlink.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asmlibrarian.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asmlibrarian.cmti' '-I' '.' '-o' './asmlibrarian.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asmgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asmgen.cmti' '-I' '.' '-o' './asmgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/arg_helper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/arg_helper.cmti' '-I' '.' '-o' './arg_helper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/alias_analysis.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/alias_analysis.cmti' '-I' '.' '-o' './alias_analysis.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/afl_instrument.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/afl_instrument.cmti' '-I' '.' '-o' './afl_instrument.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/CSEgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/CSEgen.cmti' '-I' '.' '-o' './CSEgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/CSE.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/CSE.cmt' '-I' '.' '-o' './CSE.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalMod.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalMod.cmti' '-I' '.' '-o' './camlinternalMod.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalFormat.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalFormat.cmti' '-I' '.' '-o' './camlinternalFormat.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/yojson/yojson_biniou.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_inbuf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_inbuf.cmti' '-I' '.' '-o' './bi_inbuf.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_io.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_io.cmti' '-I' '.' '-o' './bi_io.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/yojson/yojson_biniou.cmti' '-I' '.' '-o' './yojson_biniou.odoc' '--parent' 'page-"yojson"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_vint.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_vint.cmti' '-I' '.' '-o' './bi_vint.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_util.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_util.cmti' '-I' '.' '-o' './bi_util.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_stream.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_stream.cmti' '-I' '.' '-o' './bi_stream.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_dump.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_dump.cmt' '-I' '.' '-o' './bi_dump.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'link' 'src-source.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref_test__Common.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compmisc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'clflags.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Cmt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Cmti.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Ident_env.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Compat.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Resolver.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Fs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Or_error.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Source_info.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Lookup_def.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'fpath.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmt_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Compile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Tools.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Find.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Errors.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Lookup_failures.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Env.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Component.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Cfrag.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Cpath.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Ident.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Lang.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Root.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Error.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Comment.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Location_.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Paths.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Paths_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Names.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Ast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Warning.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Loc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'astring.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref_test.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parse.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'profile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'result.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Arg.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Array.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__List.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Printf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Result.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'toploop.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Obj.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Int32.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typemod.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_variance.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_separability.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_immediacy.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_properties.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'includemod.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'includecore.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedtree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'diffing_with_keys.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'diffing.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ctype.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'errortrace.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'env.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'subst.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'load_path.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmi_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'misc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__String.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Digest.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'build_path_prefix_map.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'btype.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'shape.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'primitive.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'path.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'outcometree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'type_immediacy.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parsetree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'longident.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ident.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'identifiable.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Set.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Map.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Hashtbl.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asttypes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'location.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Domain.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Buffer.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Uchar.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Seq.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Either.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'warnings.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Sys.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Lexing.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Lazy.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalLazy.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib.odoc' '-I' '.' '--open=""' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalFormatBasics.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Utils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Type_of.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Subst.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Strengthen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Ref_tools.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Link.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Lang_of.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Expand_tools.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Url.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Link.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_latex__Generator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_latex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Semantics.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Html_page.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Config.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Renderer.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Reason.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__ML.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Url.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tyxml.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tyxml_html.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'html_sigs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'html_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tyxml_svg.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'svg_sigs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'svg_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tyxml_xml.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_stream.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_sigs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_wrap.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Support_files.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Source_tree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Rendering.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Odoc_link.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Odoc_file.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Man_page.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_manpage__Generator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_manpage.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Latex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Html_fragment.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Depends.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Compile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html_support_files.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc__Type_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc__Paths_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc__Lang_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc__Comment_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_semantics_test__Test.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_semantics_test.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__BytesLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Int64.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__ListLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__MoreLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Nativeint.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Printexc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__StdLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__StringLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'yojson.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_outbuf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_share.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Reference.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Predefined.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_manpage__Link.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Uid.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Local_jmp.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Doc_attr.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Cmi.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_latex__Types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_latex__Raw.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'fmt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Stack.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Queue.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Utils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Char.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Html_source.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Html_page.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Html_fragment_json.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Generator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Utils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Targets.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Generator_signatures.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Codefmt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Generator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Doctree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Compat.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Comment.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Wrapping.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Unexposed.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Resolution.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Markup.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Expansion.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Token.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Syntax.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Parse_error.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Lexer.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmdliner.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_print.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_iter.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'svg_f.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'html_f.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'fmt_tty.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'fmt_cli.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unixLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unix.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Bigarray.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Complex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'thread.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'event.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'str.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Weak.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Unit.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Semaphore.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Scanf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Random.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Parsing.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Out_channel.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Option.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Oo.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalOO.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Mutex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Marshal.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Int.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__In_channel.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Gc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Fun.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Float.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Filename.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Ephemeron.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Effect.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Condition.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Callback.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Bytes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Bool.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Atomic.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__ArrayLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'std_exit.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'runtime_events.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'profiling.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ocamlmktop_init.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topcommon.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'genprintval.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'dynlink.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_proc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_ast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_masm.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_gas.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_dsl.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'variable.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'internal_variable_names.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'debuginfo.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compilation_unit.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linkage_name.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'var_within_closure.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_element.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'untypeast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unbox_specialised_args.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inline_and_simplify_aux.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_stats_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_cost.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'backend_intf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simple_value_approx.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'freshening.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tag.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'symbol.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'static_exception.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'set_of_closures_origin.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'set_of_closures_id.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'projection.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parameter.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'numbers.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'mutable_variable.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'export_id.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_origin.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_id.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'clambda_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'allocated_const.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unbox_free_vars_of_closures.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unbox_closures.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'un_anf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'clambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'backend_var.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typetexp.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typeopt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_unboxed.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typecore.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typeclass.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'traverse_for_exported_symbols.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'export_info.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translprim.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translobj.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translmod.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translcore.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translclass.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translattribute.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'trace.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topstart.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topmain.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tophooks.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topeval.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topdirs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tmc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'terminfo.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tast_mapper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tast_iterator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'targetint.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'syntaxerr.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'symtable.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmo_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'switch.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stypes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'annot.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'strongly_connected_components.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'strmatch.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmm.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'split.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'mach.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'reg.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'arch.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'config.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'spill.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplify_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplify_common.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplify_boxed_integer_ops_intf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplify_boxed_integer_ops.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplif.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'signature_group.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'share_constants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'semantics_of_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'selection.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'selectgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'scheduling.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linear.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'schedgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'runtimedef.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'remove_unused_program_constructs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'remove_unused_closure_vars.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'remove_unused_arguments.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'remove_free_vars_equal_to_args.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'reloadgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'reload.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ref_to_variables.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'rec_check.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'proc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printtyped.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printtyp.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printpat.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printmach.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printlinear.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printlambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printinstr.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'instruct.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printcmm.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printclambda_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printclambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'predef.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'pprintast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'pparse.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'polling.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'persistent_env.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lazy_backtrack.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'consistbl.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'patterns.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'pass_wrapper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parser.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'docstrings.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalMenhirLib.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parmatch.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'optmaindriver.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'optmain.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'opterrors.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'optcompile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compile_common.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'oprint.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'opcodes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'mtype.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'meta.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'matching.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'makedepend.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'maindriver.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'main_args.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'main.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'local_store.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'liveness.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linscan.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linearize.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linear_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lift_let_to_initialize_symbol.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lift_constants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lift_code.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lexer.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'invariant_params.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'interval.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'interf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'int_replace_polymorphic_compare.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_transforms.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_decision_intf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_stats.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_decision.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inline_and_simplify.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'initialize_symbol_to_let_symbol.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inconstant_idents.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'includemod_errorprinter.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'includeclass.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'import_approx.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'id_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_utils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_to_clambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_middle_end.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_iterators.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_invariants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'find_recursive_functions.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'extract_projections.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'expunge.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytesections.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'export_info_for_pack.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'errors.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'envaux.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'emitenv.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'emitcode.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'emitaux.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'emit.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'effect_analysis.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'domainstate.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'dll.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'depend.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'deadcode.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'datarepr.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'dataflow.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'convert_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'config_main.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'config_boot.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compilenv.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmx_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compenv.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'comballoc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'coloring.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmxs_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmt2annot.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmmgen_state.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmmgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmm_invariants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmm_helpers.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_offsets.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_middle_end.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_conversion_aux.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_conversion.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ccomp.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytepackager.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytelink.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytelibrarian.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytegen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'builtin_attributes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'build_export_info.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'branch_relaxation_intf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'branch_relaxation.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'binutils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'augment_specialised_args.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'attr_helper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ast_mapper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ast_iterator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ast_invariants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ast_helper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asmpackager.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asmlink.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asmlibrarian.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asmgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'arg_helper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'alias_analysis.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'afl_instrument.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'CSEgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'CSE.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalMod.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalFormat.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'yojson_biniou.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_io.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_inbuf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_vint.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_util.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_stream.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_dump.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-deps.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc-parser.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-astring.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-cmdliner.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-fpath.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-result.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-tyxml.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-fmt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-stdlib.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-yojson.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-biniou.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_xref_test.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_xref2.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_odoc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_html_support_files.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_model_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_model.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_manpage.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_loader.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_latex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_html.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_document.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_examples.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-interface.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-contributing.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-driver.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-parent_child_spec.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-features.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-interface.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_for_authors.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-dune.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-ocamldoc_differences.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'html-generate' 'src-source.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_xref_test__Common.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compmisc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'clflags.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/cmt.pp.ml' 'odoc_loader__Cmt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/cmti.pp.ml' 'odoc_loader__Cmti.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/ident_env.pp.ml' 'odoc_loader__Ident_env.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/compat.ml' 'odoc_model__Compat.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/resolver.ml' 'odoc_odoc__Resolver.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/fs.ml' 'odoc_odoc__Fs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/or_error.ml' 'odoc_odoc__Or_error.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_odoc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/odoc_loader.pp.ml' 'odoc_loader.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/source_info.pp.ml' 'odoc_loader__Source_info.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/lookup_def.pp.ml' 'odoc_loader__Lookup_def.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_loader__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'fpath.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmt_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/compile.ml' 'odoc_xref2__Compile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/tools.ml' 'odoc_xref2__Tools.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/find.ml' 'odoc_xref2__Find.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/errors.ml' 'odoc_xref2__Errors.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/lookup_failures.ml' 'odoc_xref2__Lookup_failures.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/env.ml' 'odoc_xref2__Env.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/component.ml' 'odoc_xref2__Component.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/cfrag.ml' 'odoc_xref2__Cfrag.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/cpath.ml' 'odoc_xref2__Cpath.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/ident.ml' 'odoc_xref2__Ident.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_xref2.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/lang.ml' 'odoc_model__Lang.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/root.ml' 'odoc_model__Root.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/error.ml' 'odoc_model__Error.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/comment.ml' 'odoc_model__Comment.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/location_.ml' 'odoc_model__Location_.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/paths.ml' 'odoc_model__Paths.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/paths_types.ml' 'odoc_model__Paths_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/names.ml' 'odoc_model__Names.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Ast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Warning.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Loc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/odoc_model.ml' 'odoc_model.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_model__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'astring.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_xref_test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parse.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'profile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'result.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Arg.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Array.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__List.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Printf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Result.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'toploop.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Obj.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Int32.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typemod.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_variance.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_separability.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_immediacy.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_properties.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'includemod.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'includecore.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedtree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'diffing_with_keys.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'diffing.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ctype.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'errortrace.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'env.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'subst.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'load_path.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmi_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'misc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__String.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Digest.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'build_path_prefix_map.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'btype.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'shape.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'primitive.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'path.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'outcometree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'type_immediacy.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parsetree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'longident.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ident.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'identifiable.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Set.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Map.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Hashtbl.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asttypes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'location.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Domain.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Buffer.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Uchar.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Seq.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Either.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'warnings.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Sys.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Lexing.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Lazy.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalLazy.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalFormatBasics.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/utils.ml' 'odoc_xref2__Utils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/type_of.ml' 'odoc_xref2__Type_of.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/subst.ml' 'odoc_xref2__Subst.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/strengthen.ml' 'odoc_xref2__Strengthen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/ref_tools.ml' 'odoc_xref2__Ref_tools.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/link.ml' 'odoc_xref2__Link.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/lang_of.ml' 'odoc_xref2__Lang_of.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/expand_tools.ml' 'odoc_xref2__Expand_tools.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/url.ml' 'odoc_odoc__Url.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/link.ml' 'odoc_html__Link.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/latex/generator.ml' 'odoc_latex__Generator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_latex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/semantics.ml' 'odoc_model__Semantics.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/html_page.ml' 'odoc_odoc__Html_page.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/config.ml' 'odoc_html__Config.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/types.ml' 'odoc_html__Types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/odoc_html.ml' 'odoc_html.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_html__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/renderer.ml' 'odoc_document__Renderer.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/reason.ml' 'odoc_document__Reason.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/ML.ml' 'odoc_document__ML.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/types.ml' 'odoc_document__Types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/url.ml' 'odoc_document__Url.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_document.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tyxml.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tyxml_html.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'html_sigs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'html_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tyxml_svg.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'svg_sigs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'svg_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tyxml_xml.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_stream.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_sigs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_wrap.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/support_files.ml' 'odoc_odoc__Support_files.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/source_tree.ml' 'odoc_odoc__Source_tree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/rendering.ml' 'odoc_odoc__Rendering.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/odoc_link.ml' 'odoc_odoc__Odoc_link.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/odoc_file.ml' 'odoc_odoc__Odoc_file.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/man_page.ml' 'odoc_odoc__Man_page.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/manpage/generator.ml' 'odoc_manpage__Generator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_manpage.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/latex.ml' 'odoc_odoc__Latex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/html_fragment.ml' 'odoc_odoc__Html_fragment.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/depends.ml' 'odoc_odoc__Depends.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/compile.ml' 'odoc_odoc__Compile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html_support_files/odoc_html_support_files.ml' 'odoc_html_support_files.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model_desc/type_desc.ml' 'odoc_model_desc__Type_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_model_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model_desc/paths_desc.ml' 'odoc_model_desc__Paths_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model_desc/lang_desc.ml' 'odoc_model_desc__Lang_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model_desc/comment_desc.ml' 'odoc_model_desc__Comment_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_model_semantics_test__Test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_model_semantics_test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__BytesLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Int64.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__ListLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__MoreLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Nativeint.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Printexc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__StdLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__StringLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'yojson.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_outbuf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_share.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/reference.ml' 'odoc_model__Reference.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/predefined.ml' 'odoc_model__Predefined.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/manpage/link.ml' 'odoc_manpage__Link.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/uid.pp.ml' 'odoc_loader__Uid.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/local_jmp.pp.ml' 'odoc_loader__Local_jmp.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/doc_attr.pp.ml' 'odoc_loader__Doc_attr.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/cmi.pp.ml' 'odoc_loader__Cmi.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/latex/types.ml' 'odoc_latex__Types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/latex/raw.ml' 'odoc_latex__Raw.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'fmt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Stack.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Queue.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/utils.ml' 'odoc_html__Utils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Char.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/html_source.ml' 'odoc_html__Html_source.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/html_page.ml' 'odoc_html__Html_page.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/html_fragment_json.ml' 'odoc_html__Html_fragment_json.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/generator.ml' 'odoc_html__Generator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/utils.ml' 'odoc_document__Utils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/targets.ml' 'odoc_document__Targets.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/generator_signatures.ml' 'odoc_document__Generator_signatures.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/codefmt.ml' 'odoc_document__Codefmt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/generator.ml' 'odoc_document__Generator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/doctree.ml' 'odoc_document__Doctree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/compat.ml' 'odoc_document__Compat.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/comment.ml' 'odoc_document__Comment.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Wrapping.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Unexposed.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Resolution.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Markup.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Expansion.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Token.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Syntax.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Parse_error.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Lexer.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmdliner.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_print.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_iter.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'svg_f.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'html_f.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'fmt_tty.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'fmt_cli.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unixLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unix.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Bigarray.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Complex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'thread.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'event.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'str.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Weak.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Unit.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Semaphore.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Scanf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Random.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Parsing.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Out_channel.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Option.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Oo.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalOO.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Mutex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Marshal.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Int.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__In_channel.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Gc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Fun.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Float.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Filename.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Ephemeron.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Effect.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Condition.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Callback.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Bytes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Bool.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Atomic.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__ArrayLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'std_exit.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'runtime_events.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'profiling.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ocamlmktop_init.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topcommon.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'genprintval.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'dynlink.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_proc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_ast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_masm.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_gas.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_dsl.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'variable.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'internal_variable_names.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'debuginfo.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compilation_unit.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linkage_name.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'var_within_closure.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_element.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'untypeast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unbox_specialised_args.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inline_and_simplify_aux.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_stats_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_cost.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'backend_intf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simple_value_approx.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'freshening.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tag.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'symbol.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'static_exception.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'set_of_closures_origin.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'set_of_closures_id.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'projection.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parameter.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'numbers.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'mutable_variable.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'export_id.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_origin.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_id.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'clambda_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'allocated_const.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unbox_free_vars_of_closures.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unbox_closures.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'un_anf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'clambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'backend_var.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typetexp.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typeopt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_unboxed.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typecore.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typeclass.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'traverse_for_exported_symbols.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'export_info.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translprim.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translobj.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translmod.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translcore.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translclass.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translattribute.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'trace.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topstart.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topmain.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tophooks.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topeval.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topdirs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tmc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'terminfo.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tast_mapper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tast_iterator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'targetint.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'syntaxerr.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'symtable.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmo_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'switch.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stypes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'annot.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'strongly_connected_components.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'strmatch.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmm.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'split.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'mach.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'reg.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'arch.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'config.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'spill.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplify_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplify_common.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplify_boxed_integer_ops_intf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplify_boxed_integer_ops.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplif.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'signature_group.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'share_constants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'semantics_of_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'selection.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'selectgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'scheduling.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linear.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'schedgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'runtimedef.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'remove_unused_program_constructs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'remove_unused_closure_vars.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'remove_unused_arguments.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'remove_free_vars_equal_to_args.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'reloadgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'reload.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ref_to_variables.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'rec_check.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'proc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printtyped.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printtyp.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printpat.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printmach.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printlinear.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printlambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printinstr.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'instruct.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printcmm.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printclambda_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printclambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'predef.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'pprintast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'pparse.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'polling.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'persistent_env.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lazy_backtrack.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'consistbl.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'patterns.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'pass_wrapper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parser.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'docstrings.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalMenhirLib.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parmatch.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'optmaindriver.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'optmain.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'opterrors.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'optcompile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compile_common.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'oprint.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'opcodes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'mtype.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'meta.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'matching.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'makedepend.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'maindriver.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'main_args.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'main.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'local_store.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'liveness.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linscan.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linearize.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linear_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lift_let_to_initialize_symbol.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lift_constants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lift_code.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lexer.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'invariant_params.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'interval.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'interf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'int_replace_polymorphic_compare.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_transforms.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_decision_intf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_stats.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_decision.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inline_and_simplify.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'initialize_symbol_to_let_symbol.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inconstant_idents.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'includemod_errorprinter.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'includeclass.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'import_approx.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'id_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_utils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_to_clambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_middle_end.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_iterators.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_invariants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'find_recursive_functions.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'extract_projections.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'expunge.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytesections.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'export_info_for_pack.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'errors.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'envaux.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'emitenv.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'emitcode.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'emitaux.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'emit.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'effect_analysis.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'domainstate.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'dll.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'depend.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'deadcode.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'datarepr.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'dataflow.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'convert_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'config_main.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'config_boot.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compilenv.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmx_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compenv.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'comballoc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'coloring.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmxs_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmt2annot.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmmgen_state.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmmgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmm_invariants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmm_helpers.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_offsets.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_middle_end.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_conversion_aux.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_conversion.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ccomp.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytepackager.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytelink.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytelibrarian.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytegen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'builtin_attributes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'build_export_info.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'branch_relaxation_intf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'branch_relaxation.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'binutils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'augment_specialised_args.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'attr_helper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ast_mapper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ast_iterator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ast_invariants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ast_helper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asmpackager.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asmlink.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asmlibrarian.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asmgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'arg_helper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'alias_analysis.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'afl_instrument.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'CSEgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'CSE.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalMod.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalFormat.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'yojson_biniou.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_io.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_inbuf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_vint.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_util.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_stream.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_dump.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-deps.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc-parser.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-astring.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-cmdliner.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-fpath.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-result.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-tyxml.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-fmt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-stdlib.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-yojson.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-biniou.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_xref_test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_xref2.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_odoc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_html_support_files.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_model_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_model.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_manpage.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_loader.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_latex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_html.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_document.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_examples.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-interface.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-contributing.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-driver.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-parent_child_spec.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-features.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-interface.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_for_authors.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-dune.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-ocamldoc_differences.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'support-files' '-o' 'html/odoc' +- : unit = () +``` diff --git a/doc/driver.mld b/doc/driver.mld index 04a5a2a66c..07b1a6d608 100644 --- a/doc/driver.mld +++ b/doc/driver.mld @@ -4,9 +4,11 @@ This 'live' document describes how to use [odoc] to produce the documentation of to show a short, simple example of how [odoc] can be used, covering most of the important features. The document built here includes not only the documentation of [odoc] itself, but it also builds the docs for a subset of [odoc]'s dependent libraries to show how this may be done. For a much more -complete and comprehensive use of [odoc], see the {{: https://github.com/ocaml-doc/voodoo} Voodoo project}, -the tool used to build the package docs for -{{: https://ocaml.org/}ocaml.org/packages}. +complete and comprehensive use of [odoc], see the {{: https://github.com/ocaml-doc/voodoo} Voodoo project}, the tool that is being used to build +the package docs for +{{: https://ocaml.org/packages} ocaml.org/packages}. The information in this page is specific to +odoc version 2.3 or later. For earlier +versions see the [driver.md] or [driver.mld] files in the corresponding source distribution. First, we need to initialise MDX with some libraries and helpful values: @@ -20,14 +22,14 @@ open Bos;; let (>>=) = Result.bind;; let (>>|=) m f = m >>= fun x -> Ok (f x);; let get_ok = function | Ok x -> x | Error (`Msg m) -> failwith m +let relativize p = Fpath.(v ".." // p) (* this driver is run from the [doc] dir *) ]} {1 Desired Output} -[odoc] produces output files (HTML or others) in a structured directory tree, so before running [odoc], -the structure of the output must be decided. For these docs, we want the following structure: +[odoc] produces output files (HTML or others) in a structured directory tree, so before running [odoc], the structure of the output must be decided. For these docs, we want the following structure: {ul {- [odoc/index.html] : main page -}{- [odoc/\{odoc_for_authors.html,...\}] : other documentation pages +}{- [odoc/{odoc_for_authors.html,...}] : other documentation pages }{- [odoc/odoc_model/index.html] : [odoc] model library subpage }{- [odoc/odoc_model/Odoc_model/index.html] : Module page for the module [Odoc_model] }{- [odoc/odoc_model/Odoc_model/...] : Further pages for the submodules of [Odoc_model] @@ -36,52 +38,60 @@ the structure of the output must be decided. For these docs, we want the followi }{- [odoc/deps/stdlib/Stdlib/index.html] : Module page for the module [Stdlib] }{- [odoc/deps/astring/index.html] : astring main page }{- [odoc/deps/...] : other dependencies +}{- [odoc/source/...] : rendered source files }} -The [odoc] model for achieving this is that we have {e pages} ([.mld] files) that have {e children} -which are either {e further pages} ([.mld] files) or {e modules} (from [.cmti] files). -This {{!page-parent_child_spec} parent/child relationship} is specified on the command line. -Parent pages must be {e compiled} by [odoc] before their children. Then compiling a page [mypage.mld] -will produce the file [page-mypage.odoc]. +The [odoc] model for achieving this is that we have {e pages} ([.mld] files) that have {e children} which are either {e further pages} ([.mld] files), {e modules} (from [.cmti] files), or +a {e source parent}. This {{!page-parent_child_spec}parent/child relationship} is specified on the command line. Parent pages must be {e compiled} by [odoc] before their children. Then compiling a page [mypage.mld] will produce the file [page-mypage.odoc]. -In the example below, there will be a file [odoc.mld] that corresponds with the top-level directory [odoc/]. -It will be compiled as follows: +In the example below, there will be a file [odoc.mld] that corresponds with the top-level directory [odoc/]. It will be compiled as follows: {[ -odoc compile odoc.mld --child page-odoc_model --child deps ... +odoc compile odoc.mld --child page-odoc_model --child deps + --child src-source ... ]} The file [deps.mld] which corresponds with the sub-directory [odoc/deps/], will be compiled as follows: {[ -odoc compile deps.mld -I . --parent `odoc` --child page-stdlib --child page-astring ... +odoc compile deps.mld -I . --parent page-odoc --child page-stdlib --child page-astring ... ]} The file [odoc_model.mld] will have a child module [Odoc_model]. It will be compiled as follows: {[ -odoc compile odoc_model.mld -I . --parent `odoc` --child module-Odoc_model +odoc compile odoc_model.mld -I . --parent page-odoc --child module-Odoc_model ]} -When compiling any [.mld] file, the parent and all children must be specified. Parents can only -be pages from other [.mld] files, but children may be pages (from [.mld] files) or modules -(from [.cmti]/[.cmt] or [.cmi] files). +The last type of page contains a list of paths to the source files that should be rendered as HTML. The output will be found as a tree underneath this page. This will be compiled in the following way: -The parent page must exist before the child page is created, and it must have had the child specified -when it was initially compiled. +{[ +odoc source-tree source.map -I . --parent page-odoc +]} + +where the first few lines of [source.map] are: + +{[ +src/xref2/utils.ml +src/xref2/type_of.ml +src/xref2/tools.ml +]} + +indicating the desire for the rendered source of [utils.ml] to be found as the file [odoc/source/src/xref2/utils.ml.html]. + +When compiling any [.mld] file, the parent and all children must be specified. Parents can only be pages from other [.mld] files, and children may be pages (from [.mld] files) or modules (from [.cmti]/[.cmt] or [.cmi] files). + +The parent page must exist before the child page is created, and it must have had the child specified when it was initially compiled. {1 Document Generation Phases} Using [odoc] is a three-phase process: -{ol {- Compilation: [odoc compile] +{ol {- Compilation: odoc compile +}} + +This takes as input either [.mld] files containing pure odoc markup, or the output from the compiler in the form of [.cmti], [.cmt], or [.cmi] files (in order of preference). For [.mld] files, this step simply translates them into [odoc]'s internal format and writes the corresponding file. For example, given the input [foobar.mld], [odoc] will output [page-foobar.odoc]. There are no dependencies for compiling [.mld] files beyond the parent as outlined above. -This takes the output from the compiler in the form of [.cmti], [.cmt], or [.cmi] files (in order of preference), -translates it into [odoc]'s internal format, and performs some initial expansion and resolution operations. -For a given input [/path/to/file.cmti], it will output the file [/path/to/file.odoc], unless the [-o] option -is used to override the output file. If there were [.cmi] dependencies required for OCaml to compile these files, -then there will be equivalent [.odoc] dependencies needed for the [odoc compile] step. [odoc] will search for -these dependencies in the paths specified with the [-I] directive on compilation. [odoc] provides a command to -help with this: [odoc compile-deps]: +For modules, compilation is the point where [odoc] performs some initial expansion and resolution operations, a process that usually introduces dependencies. For a given input [/path/to/file.cmti] it will output the file [/path/to/file.odoc] unless the [-o] option is used to override the output file. If there were [.cmi] dependencies required for OCaml to compile a particular module, then there will be equivalent [.odoc] dependencies needed for the [odoc compile] step. [odoc] will search for these dependencies in the paths specified with the [-I] directive on compilation. [odoc] provides a command to help with this: [odoc compile-deps]. As an example we can run [odoc compile-deps] on the file [../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Compile.cmti]: @@ -94,35 +104,24 @@ Stdlib__uchar ab6f1df93abf9e800a3e0d1543523c96 Odoc_xref2__Compile e0d620d652a724705f7ed620dfe07be0 ]} -It's necessary to run [odoc compile] against several [Stdlib] modules before we can compile [odoc_xref2__Compile.cmti] -} -{- Linking: [odoc link] - +From this, we see it's necessary to run [odoc compile] against several [Stdlib] modules before we can compile [odoc_xref2__Compile.cmti] +{ol {- Linking: odoc link +}} -This takes the [odoc] files produced during the compilation step and performs the final steps of -expansion and resolution. It's during this phase that all the references in the documentation comments are -resolved. In order for these to be resolved, everything that's referenced must have been compiled already, -and their [odoc] files must be on the include path as specified by the [-I] arguments to [odoc link]. -In this example, we achieve that by compiling all modules and [.mld] files before linking anything. The output of the +This takes the [odoc] files produced during the compilation step and performs the final steps of resolution for both pages and modules, and expansion for modules only. It is during this phase that all the references in the documentation comments are resolved. In order for these to be resolved, everything that is referenced must have been compiled already, and their [odoc] files must be on the +include path as specified by the [-I] arguments to [odoc link]. In this example, we achieve that by compiling all modules and [.mld] files before linking anything. The output of the link step is an [odocl] file, which is in the same path as the original [odoc] file by default. Please note: it's only necessary to link the non-hidden modules (i.e., without a double underscore). -} -{- Generation: [odoc html-generate] - - -Once the compile and link phases are complete, the resulting [odocl] files may be rendered in a variety -of formats. In this example, we output HTML: +{ol {- Generation: odoc html-generate }} +Once the compile and link phases are complete, the resulting [odocl] files may be rendered in a variety of formats. In this example we output HTML. + {1 [odoc] Documentation} -In this section, [odoc] is used to generate the documentation of [odoc] and some of its dependent packages. -We can make a few simplifying assumptions here: -{ol {- Since we're working with one leaf package, we can assume that there can be no module name -clashes in the dependencies. As such, we can afford to put all of our [.odoc] files into one directory -and then hard-code the include path to be this directory. When using [odoc] in a context where there may -be module name clashes, it requires more careful partitioning of output directories. +In this section [odoc] is used to generate the documentation of [odoc] and some of its dependent packages. We can make a few simplifying assumptions here: +{ol {- Since we're working with one leaf package, we can assume that there can be no module name clashes in the dependencies. As such, we can afford to put all of our [.odoc] files into one directory and then hard-code the include path to be this directory. When using [odoc] in a context where there may be module name clashes, it requires more careful partitioning of output directories. }{- We'll do all of the compiling before any linking. }} @@ -130,18 +129,25 @@ Let's start with some functions to execute the three phases of [odoc]. Compiling a file with [odoc] requires a few arguments: the file to compile, an optional parent, a list of include paths, a list of children for [.mld] files, -and an output path. Include paths can be just ['.'], and we can calculate the -output file from the input because all of the files are going into the same directory. +optional parent and name for source implementation, and an output path. Include +paths can be just ['.'], and we can calculate the output file from the input +because all of the files are going into the same directory. Linking a file with [odoc] requires the input file and a list of include paths. As for compile, we will hard-code the include path. -Generating the HTML requires the input [odocl] file and an output path. We will hard-code the output path to be [html]. +Generating the HTML requires the input [odocl] file, an optional implementation +source file (passed via the [--source] argument), and an output path. We will +hard-code the output path to be [html/]. + +Using the [--source] argument with an [.odocl] file that was not compiled with +[--source-parent-file] and [--source-name] will result in an error, as will omitting [--source] when generating HTML of an [odocl] that was +compiled with [--source-parent-file] and [--source-name]. In all of these, we'll capture [stdout] and [stderr] so we can check it later. {[ -let odoc = Cmd.v "../src/odoc/bin/main.exe" +let odoc = Cmd.v "../src/odoc/bin/main.exe" (* This is the just-built odoc binary *) let compile_output = ref [ "" ] @@ -149,13 +155,21 @@ let link_output = ref [ "" ] let generate_output = ref [ "" ] +let commands = ref [ ] + +let run cmd = + let cmd_str = Cmd.to_string cmd in + commands := cmd_str :: !commands; + OS.Cmd.(run_out ~err:OS.Cmd.err_run_out cmd |> to_lines) |> get_ok + let add_prefixed_output cmd list prefix lines = if List.length lines > 0 then list := !list @ Bos.Cmd.to_string cmd :: List.map (fun l -> prefix ^ ": " ^ l) lines -let compile file ?parent ?(ignore_output = false) children = +let compile file ?parent ?(output_dir = Fpath.v "./") + ?(ignore_output = false) ?source_args children = let output_file = let ext = Fpath.get_ext file in let basename = Fpath.basename (Fpath.rem_ext file) in @@ -165,8 +179,18 @@ let compile file ?parent ?(ignore_output = false) children = | _ -> failwith ("bad extension: " ^ ext) in let open Cmd in + let source_args = + match source_args with + | None -> Cmd.empty + | Some (source_name, source_parent_file) -> + Cmd.( + v "--source-name" % p source_name % "--source-parent-file" + % p source_parent_file) + in let cmd = - odoc % "compile" % Fpath.to_string file % "-I" % "." % "-o" % output_file + odoc % "compile" % Fpath.to_string file %% source_args % "-I" % "." + % "-o" + % p (Fpath.( / ) output_dir output_file) |> List.fold_right (fun child cmd -> cmd % "--child" % child) children in let cmd = @@ -174,7 +198,7 @@ let compile file ?parent ?(ignore_output = false) children = | Some p -> cmd % "--parent" % ("page-\"" ^ p ^ "\"") | None -> cmd in - let lines = OS.Cmd.(run_out ~err:err_run_out cmd |> to_lines) |> get_ok in + let lines = run cmd in if not ignore_output then add_prefixed_output cmd compile_output (Fpath.to_string file) lines @@ -182,36 +206,38 @@ let link ?(ignore_output = false) file = let open Cmd in let cmd = odoc % "link" % p file % "-I" % "." in let cmd = if Fpath.to_string file = "stdlib.odoc" then cmd % "--open=\"\"" else cmd in - Format.printf "%a" pp cmd;let lines = OS.Cmd.(run_out ~err:err_run_out cmd |> to_lines) |> get_ok in + let lines = run cmd in if not ignore_output then add_prefixed_output cmd link_output (Fpath.to_string file) lines -let html_generate ?(ignore_output = false) file = +let html_generate ?(ignore_output = false) file source = let open Cmd in + let source = match source with None -> empty | Some source -> v "--source" % p source in let cmd = - odoc % "html-generate" % p file % "-o" % "html" % "--theme-uri" % "odoc" + odoc % "html-generate" %% source % p file % "-o" % "html" % "--theme-uri" % "odoc" % "--support-uri" % "odoc" in - let lines = OS.Cmd.(run_out cmd ~err:err_run_out |> to_lines) |> get_ok in + let lines = run cmd in if not ignore_output then add_prefixed_output cmd generate_output (Fpath.to_string file) lines let support_files () = let open Cmd in let cmd = odoc % "support-files" % "-o" % "html/odoc" in - OS.Cmd.(run_out cmd |> to_lines) |> get_ok + run cmd ]} -We'll now make some library lists. We have not only external dependency libraries, but -[odoc] itself is also separated into libraries. These two sets of libraries will be -documented in different sections, so we'll keep them in separate lists. -Additionally we'll construct a list containing the extra documentation pages. Finally, -let's create a list mapping the section to its parent, which matches +We'll now make some library lists. We have not only external dependency +libraries, but [odoc] itself is also separated into libraries. These two +sets of libraries will be documented in different sections, so we'll keep them +in separate lists. Moreover, [odoc] libraries will include the source code, via +a hardcoded path. + +Additionally we'll also construct a list containing the extra documentation pages. Finally let's create a list mapping the section to its parent, which matches the hierarchy declared above. {[ -let dep_libraries_core = - [ +let dep_libraries_core = [ "odoc-parser"; "astring"; "cmdliner"; @@ -222,10 +248,9 @@ let dep_libraries_core = "stdlib"; "yojson"; "biniou"; - ] +];; -let extra_deps = - [ +let extra_deps = [ "base"; "core_kernel"; "bin_prot"; @@ -234,67 +259,68 @@ let extra_deps = "base_quickcheck"; "ppx_sexp_conv"; "ppx_hash"; - ] +] let dep_libraries = - match Sys.getenv_opt "ODOC_BENCHMARK" with - | Some "true" -> dep_libraries_core @ extra_deps - | _ -> dep_libraries_core - -let odoc_libraries = - [ - "odoc_xref_test"; - "odoc_xref2"; - "odoc_odoc"; - "odoc_model_desc"; - "odoc_model"; - "odoc_manpage"; - "odoc_loader"; - "odoc_latex"; - "odoc_html"; - "odoc_document"; - "odoc_examples"; - ] - -let all_libraries = dep_libraries @ odoc_libraries - -let extra_docs = - [ + match Sys.getenv_opt "ODOC_BENCHMARK" with + | Some "true" -> dep_libraries_core @ extra_deps + | _ -> dep_libraries_core + +let odoc_libraries = [ + "odoc_xref_test"; "odoc_xref2"; "odoc_odoc"; "odoc_html_support_files"; + "odoc_model_desc"; "odoc_model"; "odoc_manpage"; "odoc_loader"; + "odoc_latex"; "odoc_html"; "odoc_document"; "odoc_examples" ];; + +let all_libraries = dep_libraries @ odoc_libraries;; + +let extra_docs = [ "interface"; "contributing"; "driver"; "parent_child_spec"; "features"; - "dune_wrapping"; "interface"; "odoc_for_authors"; "dune"; "ocamldoc_differences"; - ] +] let parents = - let add_parent p l = List.map (fun lib -> (lib, p)) l in - add_parent "deps" dep_libraries @ add_parent "odoc" odoc_libraries + let add_parent p l = List.map (fun lib -> (lib, p)) l in + (add_parent "deps" dep_libraries) @ (add_parent "odoc" odoc_libraries);; + ]} -[odoc] operates on the compiler outputs. We need to find them for both the files -compiled by Dune within this project and those in libraries we compile against. -The following uses [ocamlfind] to locate the library paths for our dependencies: +[odoc] operates on the compiler outputs. We need to find them for both the files compiled by Dune within this project and those in libraries we compile against. +The following uses [ocamlfind] to locate the library paths for our dependencies. Since [ocamlfind] gives +us the absolute path, we also have a short function here to relativize it based on our current working +directory to ensure the log of commands we collect is as reproducible as possible. {[ let ocamlfind = Cmd.v "ocamlfind" +let reach t ~from = + let rec loop t from = + match (t, from) with + | a :: t, b :: from when a = b -> loop t from + | _ -> List.fold_right (fun _ acc -> ".." :: acc) from t + in + let v s = String.split_on_char '/' s in + loop (v t) (v from) |> String.concat "/" + +let relativize_path = + let pwd = Sys.getcwd () in + fun p -> reach p ~from:pwd + let lib_path lib = let cmd = Cmd.(ocamlfind % "query" % lib) in - OS.Cmd.(run_out cmd |> to_lines >>|= List.hd) + run cmd |> List.hd |> relativize_path let lib_paths = List.fold_right (fun lib acc -> - acc >>= fun acc -> - lib_path lib >>|= fun l -> (lib, l) :: acc) - dep_libraries (Ok []) - |> get_ok + (lib, lib_path lib) :: acc) + dep_libraries [] ]} We need a function to find [odoc] inputs from the given search path. [odoc] @@ -318,7 +344,8 @@ let find_units p = not @@ Astring.String.is_infix ~affix:"ocamldoc" (Fpath.to_string f)) l in - List.fold_right Fpath.Set.add l Fpath.Set.empty]} + List.fold_right Fpath.Set.add l Fpath.Set.empty;; +]} Since the units returned by this function have their extension stripped, we need function to find the best file to use with this basename. @@ -338,8 +365,7 @@ a module is intended to be hidden. The following predicate tests for that condit let is_hidden path = Astring.String.is_infix ~affix:"__" (Fpath.to_string path) ]} -To build the documentation, we start with these files. With the following function, we'll -call [odoc compile-deps] on the file to +To build the documentation, we start with these files. With the following function, we'll call [odoc compile-deps] on the file to find all other compilation units upon which it depends: {[ @@ -347,15 +373,79 @@ type compile_deps = { digest : Digest.t; deps : (string * Digest.t) list } let compile_deps f = let cmd = Cmd.(odoc % "compile-deps" % Fpath.to_string f) in - OS.Cmd.(run_out cmd |> to_lines) - >>|= List.filter_map (Astring.String.cut ~sep:" ") - >>= fun l -> + let deps = run cmd in + let l = List.filter_map (Astring.String.cut ~sep:" ") deps in let basename = Fpath.(basename (f |> rem_ext)) |> String.capitalize_ascii in match List.partition (fun (n, _) -> basename = n) l with | [ (_, digest) ], deps -> Ok { digest; deps } | _ -> Error (`Msg "odd") ]} +For [odoc] libraries, we infer the implementation and interface source file path +from the library name. We list them in a file, passed to [odoc source-tree], to +generate [src-source.odoc]. This file contains the source hierarchy, and will be +linked and passed to [html-generate] just as other pages and compilation units. + +It is used as the [source-parent] for all units for which we could provide +sources. + +{[ +let source_tree_output = ref [ "" ] + +let source_tree ?(ignore_output = false) ~parent ~output file = + let open Cmd in + let parent = v "--parent" % ("page-\"" ^ parent ^ "\"") in + let cmd = odoc % "source-tree" % "-I" % "." %% parent % "-o" % p output % p file in + let lines = run cmd in + if not ignore_output then + add_prefixed_output cmd source_tree_output (Fpath.to_string file) lines + +let odoc_source_tree = Fpath.v "src-source.odoc" + +let source_dir_of_odoc_lib lib = + match String.split_on_char '_' lib with + | "odoc" :: s -> + let libname = Fpath.(v (String.concat "_" s)) in + Some Fpath.(v "src" // libname) + | _ -> None + +let source_files_of_odoc_module lib module_ = + let filename = + let module_ = + match Astring.String.cut ~rev:true ~sep:"__" module_ with + | None -> module_ + | Some (_, "") -> module_ + | Some (_, module_) -> module_ + in + (* ML.ml should not be renamed *) + if String.for_all (fun c -> Char.equal (Char.uppercase_ascii c) c) module_ + then module_ + else String.uncapitalize_ascii module_ + in + match source_dir_of_odoc_lib lib with + | None -> None + | Some relpath -> + let add_filename path ext = + Fpath.( / ) path filename |> Fpath.add_ext ext + in + let find_by_extension path exts = + exts + |> List.map (fun ext -> add_filename path ext) + |> List.find_opt (fun f -> Bos.OS.File.exists (relativize f) |> get_ok) + in + find_by_extension relpath [ "pp.ml"; "ml" ] + +let compile_source_tree units = + let sources = + List.filter_map (fun (_, _, _, file) -> Option.map Fpath.to_string file) units + in + let source_map = Fpath.v "source.map" in + let () = Bos.OS.File.write_lines source_map sources |> get_ok in + let () = source_tree ~parent:"odoc" ~output:odoc_source_tree source_map in + (odoc_source_tree, false, None) + +]} + Let's now put together a list of all possible modules. We'll keep track of which library they're in, and whether that library is a part of [odoc] or a dependency library. @@ -369,7 +459,11 @@ let odoc_units = Fpath.Set.fold (fun p acc -> if Astring.String.is_infix ~affix:lib (Fpath.to_string p) then - ("odoc", lib, p) :: acc + let impl = + let module_ = Fpath.basename p in + source_files_of_odoc_module lib module_ + in + ("odoc", lib, p, impl) :: acc else acc) odoc_all_unit_paths []) odoc_libraries @@ -381,16 +475,14 @@ let all_units = List.map (fun (lib, p) -> Fpath.Set.fold - (fun p acc -> ("deps", lib, p) :: acc) + (fun p acc -> ("deps", lib, p, None) :: acc) (find_units p |> get_ok) []) lib_paths in odoc_units @ lib_units |> List.flatten ]} -Now we'll compile all of the parent [.mld] files. To ensure that the parents are -compiled before the children, we start with [odoc.mld], then [deps.mld], and so on. The result -of this file is a list of the resulting [odoc] files. +Now we'll compile all of the parent [.mld] files. To ensure that the parents are compiled before the children, we start with [odoc.mld], then [deps.mld], and so on. The result of this file is a list of the resulting [odoc] files. {[ let compile_mlds () = @@ -399,7 +491,7 @@ let compile_mlds () = let mkmld x = Fpath.(add_ext "mld" (v x)) in ignore (compile (mkmld "odoc") - ("page-deps" :: List.map mkpage (odoc_libraries @ extra_docs))); + ("src-source" :: "page-deps" :: List.map mkpage (odoc_libraries @ extra_docs))); ignore (compile (mkmld "deps") ~parent:"odoc" (List.map mkpage dep_libraries)); let extra_odocs = List.map @@ -414,32 +506,30 @@ let compile_mlds () = let parent = List.assoc library parents in let children = List.filter_map - (fun (parent, lib, child) -> + (fun (parent, lib, child, _) -> if lib = library then Some (Fpath.basename child |> mkmod) else None) all_units in - ignore (compile (mkmld library) ~parent children); + ignore (compile (mkmld ("library_mlds/"^library)) ~parent children); "page-" ^ library ^ ".odoc") all_libraries in List.map - (fun f -> (Fpath.v f, false)) + (fun f -> (Fpath.v f, false, None)) ("page-odoc.odoc" :: "page-deps.odoc" :: odocs @ extra_odocs) ]} -Now we get to the compilation phase. For each unit, we query its dependencies, -then recursively call to compile these dependencies. Once this is done, we compile the unit itself. -If the unit has already been compiled, we don't do anything. Note that we aren't checking the -hashes of the dependencies which a build system should do to ensure that the module being compiled -is the correct one. Again, we benefit from the fact that we're creating the docs for one -leaf package and that there must be no module name clashes in its dependencies. The result -of this function is a list of the resulting [odoc] files. +Now we get to the compilation phase. For each unit, we query its dependencies, then recursively call to compile these dependencies. Once this is done we compile the unit itself. If the unit has already been compiled we don't do anything. Note that we aren't checking the hashes of the dependencies which a build system should do to ensure that the module being compiled is the correct one. Again we benefit from the fact that we're creating the docs for one leaf package and that there must be no module name clashes in its dependencies. The result of this function is a list of the resulting [odoc] files. {[ let compile_all () = let mld_odocs = compile_mlds () in - let rec rec_compile parent lib file = + let source_tree = compile_source_tree all_units in + let source_args = + Option.map (fun source_relpath -> (source_relpath, odoc_source_tree)) + in + let rec rec_compile ?impl parent lib file = let output = Fpath.(base (set_ext "odoc" file)) in if OS.File.exists output |> get_ok then [] else @@ -449,45 +539,47 @@ let compile_all () = (fun acc (dep_name, digest) -> match List.find_opt - (fun (_, _, f) -> + (fun (_, _, f, _) -> Fpath.basename f |> String.capitalize_ascii = dep_name) all_units with | None -> acc - | Some (parent, lib, dep_path) -> + | Some (parent, lib, dep_path, impl) -> let file = best_file dep_path in - rec_compile parent lib file @ acc) + rec_compile ?impl parent lib file @ acc) [] deps.deps in let ignore_output = parent = "deps" in - ignore (compile file ~parent:lib ~ignore_output []); - (output, ignore_output) :: files + let source_args = source_args impl in + compile file ~parent:lib ?source_args ~ignore_output []; + (output, ignore_output, impl) :: files in - List.fold_left - (fun acc (parent, lib, dep) -> acc @ rec_compile parent lib (best_file dep)) + source_tree + :: List.fold_left + (fun acc (parent, lib, dep, impl) -> + acc @ rec_compile ?impl parent lib (best_file dep)) [] all_units @ mld_odocs ]} -Linking is now straightforward. We only need to link non-hidden [odoc] files, as -any hidden ones are almost certainly aliased inside the non-hidden ones -(a result of namespacing, usually, and these aliases will be expanded). +Linking is now straightforward. We link all [odoc] files. {[ let link_all odoc_files = - let not_hidden (f, _) = not (is_hidden f) in List.map - (fun (odoc_file, ignore_output) -> + (fun (odoc_file, ignore_output, source) -> ignore (link ~ignore_output odoc_file); - Fpath.set_ext "odocl" odoc_file) - (List.filter not_hidden odoc_files) + Fpath.set_ext "odocl" odoc_file, source) + odoc_files ]} Now we simply run [odoc html-generate] over all of the resulting [odocl] files. +This will generate sources, as well as documentation for non-hidden units. {[ let generate_all odocl_files = - List.iter (fun f -> ignore(html_generate f)) odocl_files; + let relativize_opt = function None -> None | Some file -> Some (relativize file) in + List.iter (fun (f, source) -> ignore(html_generate f (relativize_opt source))) odocl_files; support_files () ]} @@ -506,12 +598,2227 @@ Let's see if there was any output from the [odoc] invocations: # !compile_output;; - : string list = [""] # !link_output;; +- : string list = +[""; "'../src/odoc/bin/main.exe' 'link' 'page-deps.odoc' '-I' '.'"; + "page-deps.odoc: File \"src/fmt.mli\", line 6, characters 4-13:"; + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(Format) Couldn't find \"Format\""; + "page-deps.odoc: File \"src/fpath.mli\", line 8, characters 8-20:"; + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(Map) Couldn't find \"Map\""; + "page-deps.odoc: File \"src/fpath.mli\", line 7, characters 59-71:"; + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(Set) Couldn't find \"Set\""; + "page-deps.odoc: File \"src/fpath.mli\", line 7, characters 28-52:"; + "page-deps.odoc: Warning: Failed to resolve reference unresolvedroot(file_exts) Couldn't find \"file_exts\""] +# !source_tree_output;; - : string list = [""] # !generate_output;; - : string list = [""; - "'../src/odoc/bin/main.exe' 'html-generate' 'odoc_xref_test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc'"; - "odoc_xref_test.odocl: Warning, resolved hidden path: Odoc_model__Lang.Signature.t"; + "'../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/odoc_model.ml' 'odoc_model.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc'"; + "odoc_model.odocl: Warning, resolved hidden path: Odoc_model__.Paths_types.Identifier.source_dir_pv"; + "odoc_model.odocl: Warning, resolved hidden path: Odoc_model__.Paths_types.Identifier.source_dir"; + "odoc_model.odocl: Warning, resolved hidden path: Odoc_model__.Paths_types.Identifier.source_dir_pv"; "'../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc'"; - "odoc_examples.odocl: Warning, resolved hidden path: Odoc_examples__Unexposed.t"] + "odoc_examples.odocl: Warning, resolved hidden path: Odoc_examples__.Unexposed.t"] +]} + +We can have a look at the produced hierarchy of files, which matches the desired output. Note that source files with a [.ml.html] extension are generated for modules compiled with the [--source] option. + +{[ +$ ls html/odoc +contributing.html +deps +driver.html +dune.html +features.html +fonts +highlight.pack.js +index.html +interface.html +katex.min.css +katex.min.js +ocamldoc_differences.html +odoc.css +odoc_document +odoc_examples +odoc_for_authors.html +odoc_html +odoc_html_support_files +odoc_latex +odoc_loader +odoc_manpage +odoc_model +odoc_model_desc +odoc_odoc +odoc_xref2 +odoc_xref_test +parent_child_spec.html +source +$ ls html/odoc/deps +astring +biniou +cmdliner +fmt +fpath +index.html +odoc-parser +result +stdlib +tyxml +yojson +$ find html/odoc/deps | sort | tail -n 20 +html/odoc/deps/tyxml/Xml_wrap/module-type-T/index.html +html/odoc/deps/tyxml/index.html +html/odoc/deps/yojson +html/odoc/deps/yojson/Yojson +html/odoc/deps/yojson/Yojson/Basic +html/odoc/deps/yojson/Yojson/Basic/Util +html/odoc/deps/yojson/Yojson/Basic/Util/index.html +html/odoc/deps/yojson/Yojson/Basic/index.html +html/odoc/deps/yojson/Yojson/Lexer_state +html/odoc/deps/yojson/Yojson/Lexer_state/index.html +html/odoc/deps/yojson/Yojson/Raw +html/odoc/deps/yojson/Yojson/Raw/index.html +html/odoc/deps/yojson/Yojson/Safe +html/odoc/deps/yojson/Yojson/Safe/Util +html/odoc/deps/yojson/Yojson/Safe/Util/index.html +html/odoc/deps/yojson/Yojson/Safe/index.html +html/odoc/deps/yojson/Yojson/index.html +html/odoc/deps/yojson/Yojson_biniou +html/odoc/deps/yojson/Yojson_biniou/index.html +html/odoc/deps/yojson/index.html +$ find html/odoc/odoc_html | sort +html/odoc/odoc_html +html/odoc/odoc_html/Odoc_html +html/odoc/odoc_html/Odoc_html/Config +html/odoc/odoc_html/Odoc_html/Config/index.html +html/odoc/odoc_html/Odoc_html/Generator +html/odoc/odoc_html/Odoc_html/Generator/index.html +html/odoc/odoc_html/Odoc_html/Html_fragment_json +html/odoc/odoc_html/Odoc_html/Html_fragment_json/index.html +html/odoc/odoc_html/Odoc_html/Html_page +html/odoc/odoc_html/Odoc_html/Html_page/index.html +html/odoc/odoc_html/Odoc_html/Link +html/odoc/odoc_html/Odoc_html/Link/Path +html/odoc/odoc_html/Odoc_html/Link/Path/index.html +html/odoc/odoc_html/Odoc_html/Link/index.html +html/odoc/odoc_html/Odoc_html/Types +html/odoc/odoc_html/Odoc_html/Types/index.html +html/odoc/odoc_html/Odoc_html/index.html +html/odoc/odoc_html/index.html +]} + +Finally, let's have a list of all of the commands executed during the execution of this process: + +{[ +# List.iter (Printf.printf "$ %s\n") (List.rev !commands);; +$ 'ocamlfind' 'query' 'biniou' +$ 'ocamlfind' 'query' 'yojson' +$ 'ocamlfind' 'query' 'stdlib' +$ 'ocamlfind' 'query' 'fmt' +$ 'ocamlfind' 'query' 'tyxml' +$ 'ocamlfind' 'query' 'result' +$ 'ocamlfind' 'query' 'fpath' +$ 'ocamlfind' 'query' 'cmdliner' +$ 'ocamlfind' 'query' 'astring' +$ 'ocamlfind' 'query' 'odoc-parser' +$ '../src/odoc/bin/main.exe' 'compile' 'odoc.mld' '-I' '.' '-o' './page-odoc.odoc' '--child' 'page-"ocamldoc_differences"' '--child' 'page-"dune"' '--child' 'page-"odoc_for_authors"' '--child' 'page-"interface"' '--child' 'page-"features"' '--child' 'page-"parent_child_spec"' '--child' 'page-"driver"' '--child' 'page-"contributing"' '--child' 'page-"interface"' '--child' 'page-"odoc_examples"' '--child' 'page-"odoc_document"' '--child' 'page-"odoc_html"' '--child' 'page-"odoc_latex"' '--child' 'page-"odoc_loader"' '--child' 'page-"odoc_manpage"' '--child' 'page-"odoc_model"' '--child' 'page-"odoc_model_desc"' '--child' 'page-"odoc_html_support_files"' '--child' 'page-"odoc_odoc"' '--child' 'page-"odoc_xref2"' '--child' 'page-"odoc_xref_test"' '--child' 'page-deps' '--child' 'src-source' +$ '../src/odoc/bin/main.exe' 'compile' 'deps.mld' '-I' '.' '-o' './page-deps.odoc' '--child' 'page-"biniou"' '--child' 'page-"yojson"' '--child' 'page-"stdlib"' '--child' 'page-"fmt"' '--child' 'page-"tyxml"' '--child' 'page-"result"' '--child' 'page-"fpath"' '--child' 'page-"cmdliner"' '--child' 'page-"astring"' '--child' 'page-"odoc-parser"' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'interface.mld' '-I' '.' '-o' './page-interface.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'contributing.mld' '-I' '.' '-o' './page-contributing.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'driver.mld' '-I' '.' '-o' './page-driver.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'parent_child_spec.mld' '-I' '.' '-o' './page-parent_child_spec.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'features.mld' '-I' '.' '-o' './page-features.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'interface.mld' '-I' '.' '-o' './page-interface.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'odoc_for_authors.mld' '-I' '.' '-o' './page-odoc_for_authors.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'dune.mld' '-I' '.' '-o' './page-dune.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'ocamldoc_differences.mld' '-I' '.' '-o' './page-ocamldoc_differences.odoc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc-parser.mld' '-I' '.' '-o' './page-odoc-parser.odoc' '--child' 'module-Odoc_parser' '--child' 'module-Odoc_parser__' '--child' 'module-Odoc_parser__Ast' '--child' 'module-Odoc_parser__Lexer' '--child' 'module-Odoc_parser__Loc' '--child' 'module-Odoc_parser__Parse_error' '--child' 'module-Odoc_parser__Syntax' '--child' 'module-Odoc_parser__Token' '--child' 'module-Odoc_parser__Warning' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/astring.mld' '-I' '.' '-o' './page-astring.odoc' '--child' 'module-Astring' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/cmdliner.mld' '-I' '.' '-o' './page-cmdliner.odoc' '--child' 'module-Cmdliner' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/fpath.mld' '-I' '.' '-o' './page-fpath.odoc' '--child' 'module-Fpath' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/result.mld' '-I' '.' '-o' './page-result.odoc' '--child' 'module-Result' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/tyxml.mld' '-I' '.' '-o' './page-tyxml.odoc' '--child' 'module-Html_f' '--child' 'module-Html_sigs' '--child' 'module-Html_types' '--child' 'module-Svg_f' '--child' 'module-Svg_sigs' '--child' 'module-Svg_types' '--child' 'module-Xml_iter' '--child' 'module-Xml_print' '--child' 'module-Xml_sigs' '--child' 'module-Xml_stream' '--child' 'module-Xml_wrap' '--child' 'module-Tyxml' '--child' 'module-Tyxml_html' '--child' 'module-Tyxml_svg' '--child' 'module-Tyxml_xml' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/fmt.mld' '-I' '.' '-o' './page-fmt.odoc' '--child' 'module-Fmt' '--child' 'module-Fmt_cli' '--child' 'module-Fmt_tty' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/stdlib.mld' '-I' '.' '-o' './page-stdlib.odoc' '--child' 'module-CamlinternalFormat' '--child' 'module-CamlinternalFormatBasics' '--child' 'module-CamlinternalLazy' '--child' 'module-CamlinternalMod' '--child' 'module-CamlinternalOO' '--child' 'module-CSE' '--child' 'module-CSEgen' '--child' 'module-Afl_instrument' '--child' 'module-Alias_analysis' '--child' 'module-Allocated_const' '--child' 'module-Annot' '--child' 'module-Arch' '--child' 'module-Arg_helper' '--child' 'module-Asmgen' '--child' 'module-Asmlibrarian' '--child' 'module-Asmlink' '--child' 'module-Asmpackager' '--child' 'module-Ast_helper' '--child' 'module-Ast_invariants' '--child' 'module-Ast_iterator' '--child' 'module-Ast_mapper' '--child' 'module-Asttypes' '--child' 'module-Attr_helper' '--child' 'module-Augment_specialised_args' '--child' 'module-Backend_intf' '--child' 'module-Backend_var' '--child' 'module-Binutils' '--child' 'module-Branch_relaxation' '--child' 'module-Branch_relaxation_intf' '--child' 'module-Btype' '--child' 'module-Build_export_info' '--child' 'module-Build_path_prefix_map' '--child' 'module-Builtin_attributes' '--child' 'module-Bytegen' '--child' 'module-Bytelibrarian' '--child' 'module-Bytelink' '--child' 'module-Bytepackager' '--child' 'module-Bytesections' '--child' 'module-CamlinternalMenhirLib' '--child' 'module-Ccomp' '--child' 'module-Clambda' '--child' 'module-Clambda_primitives' '--child' 'module-Clflags' '--child' 'module-Closure' '--child' 'module-Closure_conversion' '--child' 'module-Closure_conversion_aux' '--child' 'module-Closure_element' '--child' 'module-Closure_id' '--child' 'module-Closure_middle_end' '--child' 'module-Closure_offsets' '--child' 'module-Closure_origin' '--child' 'module-Cmi_format' '--child' 'module-Cmm' '--child' 'module-Cmm_helpers' '--child' 'module-Cmm_invariants' '--child' 'module-Cmmgen' '--child' 'module-Cmmgen_state' '--child' 'module-Cmo_format' '--child' 'module-Cmt2annot' '--child' 'module-Cmt_format' '--child' 'module-Cmx_format' '--child' 'module-Cmxs_format' '--child' 'module-Coloring' '--child' 'module-Comballoc' '--child' 'module-Compenv' '--child' 'module-Compilation_unit' '--child' 'module-Compile' '--child' 'module-Compile_common' '--child' 'module-Compilenv' '--child' 'module-Compmisc' '--child' 'module-Config' '--child' 'module-Config_boot' '--child' 'module-Config_main' '--child' 'module-Consistbl' '--child' 'module-Convert_primitives' '--child' 'module-Ctype' '--child' 'module-Dataflow' '--child' 'module-Datarepr' '--child' 'module-Deadcode' '--child' 'module-Debuginfo' '--child' 'module-Depend' '--child' 'module-Diffing' '--child' 'module-Diffing_with_keys' '--child' 'module-Dll' '--child' 'module-Docstrings' '--child' 'module-Domainstate' '--child' 'module-Effect_analysis' '--child' 'module-Emit' '--child' 'module-Emitaux' '--child' 'module-Emitcode' '--child' 'module-Emitenv' '--child' 'module-Env' '--child' 'module-Envaux' '--child' 'module-Errors' '--child' 'module-Errortrace' '--child' 'module-Export_id' '--child' 'module-Export_info' '--child' 'module-Export_info_for_pack' '--child' 'module-Expunge' '--child' 'module-Extract_projections' '--child' 'module-Find_recursive_functions' '--child' 'module-Flambda' '--child' 'module-Flambda_invariants' '--child' 'module-Flambda_iterators' '--child' 'module-Flambda_middle_end' '--child' 'module-Flambda_to_clambda' '--child' 'module-Flambda_utils' '--child' 'module-Freshening' '--child' 'module-Genprintval' '--child' 'module-Id_types' '--child' 'module-Ident' '--child' 'module-Identifiable' '--child' 'module-Import_approx' '--child' 'module-Includeclass' '--child' 'module-Includecore' '--child' 'module-Includemod' '--child' 'module-Includemod_errorprinter' '--child' 'module-Inconstant_idents' '--child' 'module-Initialize_symbol_to_let_symbol' '--child' 'module-Inline_and_simplify' '--child' 'module-Inline_and_simplify_aux' '--child' 'module-Inlining_cost' '--child' 'module-Inlining_decision' '--child' 'module-Inlining_decision_intf' '--child' 'module-Inlining_stats' '--child' 'module-Inlining_stats_types' '--child' 'module-Inlining_transforms' '--child' 'module-Instruct' '--child' 'module-Int_replace_polymorphic_compare' '--child' 'module-Interf' '--child' 'module-Internal_variable_names' '--child' 'module-Interval' '--child' 'module-Invariant_params' '--child' 'module-Lambda' '--child' 'module-Lazy_backtrack' '--child' 'module-Lexer' '--child' 'module-Lift_code' '--child' 'module-Lift_constants' '--child' 'module-Lift_let_to_initialize_symbol' '--child' 'module-Linear' '--child' 'module-Linear_format' '--child' 'module-Linearize' '--child' 'module-Linkage_name' '--child' 'module-Linscan' '--child' 'module-Liveness' '--child' 'module-Load_path' '--child' 'module-Local_store' '--child' 'module-Location' '--child' 'module-Longident' '--child' 'module-Mach' '--child' 'module-Main' '--child' 'module-Main_args' '--child' 'module-Maindriver' '--child' 'module-Makedepend' '--child' 'module-Matching' '--child' 'module-Meta' '--child' 'module-Misc' '--child' 'module-Mtype' '--child' 'module-Mutable_variable' '--child' 'module-Numbers' '--child' 'module-Opcodes' '--child' 'module-Oprint' '--child' 'module-Optcompile' '--child' 'module-Opterrors' '--child' 'module-Optmain' '--child' 'module-Optmaindriver' '--child' 'module-Outcometree' '--child' 'module-Parameter' '--child' 'module-Parmatch' '--child' 'module-Parse' '--child' 'module-Parser' '--child' 'module-Parsetree' '--child' 'module-Pass_wrapper' '--child' 'module-Path' '--child' 'module-Patterns' '--child' 'module-Persistent_env' '--child' 'module-Polling' '--child' 'module-Pparse' '--child' 'module-Pprintast' '--child' 'module-Predef' '--child' 'module-Primitive' '--child' 'module-Printast' '--child' 'module-Printclambda' '--child' 'module-Printclambda_primitives' '--child' 'module-Printcmm' '--child' 'module-Printinstr' '--child' 'module-Printlambda' '--child' 'module-Printlinear' '--child' 'module-Printmach' '--child' 'module-Printpat' '--child' 'module-Printtyp' '--child' 'module-Printtyped' '--child' 'module-Proc' '--child' 'module-Profile' '--child' 'module-Projection' '--child' 'module-Rec_check' '--child' 'module-Ref_to_variables' '--child' 'module-Reg' '--child' 'module-Reload' '--child' 'module-Reloadgen' '--child' 'module-Remove_free_vars_equal_to_args' '--child' 'module-Remove_unused_arguments' '--child' 'module-Remove_unused_closure_vars' '--child' 'module-Remove_unused_program_constructs' '--child' 'module-Runtimedef' '--child' 'module-Schedgen' '--child' 'module-Scheduling' '--child' 'module-Selectgen' '--child' 'module-Selection' '--child' 'module-Semantics_of_primitives' '--child' 'module-Set_of_closures_id' '--child' 'module-Set_of_closures_origin' '--child' 'module-Shape' '--child' 'module-Share_constants' '--child' 'module-Signature_group' '--child' 'module-Simple_value_approx' '--child' 'module-Simplif' '--child' 'module-Simplify_boxed_integer_ops' '--child' 'module-Simplify_boxed_integer_ops_intf' '--child' 'module-Simplify_common' '--child' 'module-Simplify_primitives' '--child' 'module-Spill' '--child' 'module-Split' '--child' 'module-Static_exception' '--child' 'module-Strmatch' '--child' 'module-Strongly_connected_components' '--child' 'module-Stypes' '--child' 'module-Subst' '--child' 'module-Switch' '--child' 'module-Symbol' '--child' 'module-Symtable' '--child' 'module-Syntaxerr' '--child' 'module-Tag' '--child' 'module-Targetint' '--child' 'module-Tast_iterator' '--child' 'module-Tast_mapper' '--child' 'module-Terminfo' '--child' 'module-Tmc' '--child' 'module-Topcommon' '--child' 'module-Topdirs' '--child' 'module-Topeval' '--child' 'module-Tophooks' '--child' 'module-Toploop' '--child' 'module-Topmain' '--child' 'module-Topstart' '--child' 'module-Trace' '--child' 'module-Translattribute' '--child' 'module-Translclass' '--child' 'module-Translcore' '--child' 'module-Translmod' '--child' 'module-Translobj' '--child' 'module-Translprim' '--child' 'module-Traverse_for_exported_symbols' '--child' 'module-Type_immediacy' '--child' 'module-Typeclass' '--child' 'module-Typecore' '--child' 'module-Typedecl' '--child' 'module-Typedecl_immediacy' '--child' 'module-Typedecl_properties' '--child' 'module-Typedecl_separability' '--child' 'module-Typedecl_unboxed' '--child' 'module-Typedecl_variance' '--child' 'module-Typedtree' '--child' 'module-Typemod' '--child' 'module-Typeopt' '--child' 'module-Types' '--child' 'module-Typetexp' '--child' 'module-Un_anf' '--child' 'module-Unbox_closures' '--child' 'module-Unbox_free_vars_of_closures' '--child' 'module-Unbox_specialised_args' '--child' 'module-Untypeast' '--child' 'module-Var_within_closure' '--child' 'module-Variable' '--child' 'module-Warnings' '--child' 'module-X86_ast' '--child' 'module-X86_dsl' '--child' 'module-X86_gas' '--child' 'module-X86_masm' '--child' 'module-X86_proc' '--child' 'module-Dynlink' '--child' 'module-Ocamlmktop_init' '--child' 'module-Profiling' '--child' 'module-Runtime_events' '--child' 'module-Std_exit' '--child' 'module-Stdlib' '--child' 'module-Stdlib__Arg' '--child' 'module-Stdlib__Array' '--child' 'module-Stdlib__ArrayLabels' '--child' 'module-Stdlib__Atomic' '--child' 'module-Stdlib__Bigarray' '--child' 'module-Stdlib__Bool' '--child' 'module-Stdlib__Buffer' '--child' 'module-Stdlib__Bytes' '--child' 'module-Stdlib__BytesLabels' '--child' 'module-Stdlib__Callback' '--child' 'module-Stdlib__Char' '--child' 'module-Stdlib__Complex' '--child' 'module-Stdlib__Condition' '--child' 'module-Stdlib__Digest' '--child' 'module-Stdlib__Domain' '--child' 'module-Stdlib__Effect' '--child' 'module-Stdlib__Either' '--child' 'module-Stdlib__Ephemeron' '--child' 'module-Stdlib__Filename' '--child' 'module-Stdlib__Float' '--child' 'module-Stdlib__Format' '--child' 'module-Stdlib__Fun' '--child' 'module-Stdlib__Gc' '--child' 'module-Stdlib__Hashtbl' '--child' 'module-Stdlib__In_channel' '--child' 'module-Stdlib__Int' '--child' 'module-Stdlib__Int32' '--child' 'module-Stdlib__Int64' '--child' 'module-Stdlib__Lazy' '--child' 'module-Stdlib__Lexing' '--child' 'module-Stdlib__List' '--child' 'module-Stdlib__ListLabels' '--child' 'module-Stdlib__Map' '--child' 'module-Stdlib__Marshal' '--child' 'module-Stdlib__MoreLabels' '--child' 'module-Stdlib__Mutex' '--child' 'module-Stdlib__Nativeint' '--child' 'module-Stdlib__Obj' '--child' 'module-Stdlib__Oo' '--child' 'module-Stdlib__Option' '--child' 'module-Stdlib__Out_channel' '--child' 'module-Stdlib__Parsing' '--child' 'module-Stdlib__Printexc' '--child' 'module-Stdlib__Printf' '--child' 'module-Stdlib__Queue' '--child' 'module-Stdlib__Random' '--child' 'module-Stdlib__Result' '--child' 'module-Stdlib__Scanf' '--child' 'module-Stdlib__Semaphore' '--child' 'module-Stdlib__Seq' '--child' 'module-Stdlib__Set' '--child' 'module-Stdlib__Stack' '--child' 'module-Stdlib__StdLabels' '--child' 'module-Stdlib__String' '--child' 'module-Stdlib__StringLabels' '--child' 'module-Stdlib__Sys' '--child' 'module-Stdlib__Uchar' '--child' 'module-Stdlib__Unit' '--child' 'module-Stdlib__Weak' '--child' 'module-Str' '--child' 'module-Event' '--child' 'module-Thread' '--child' 'module-Unix' '--child' 'module-UnixLabels' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/yojson.mld' '-I' '.' '-o' './page-yojson.odoc' '--child' 'module-Yojson' '--child' 'module-Yojson_biniou' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/biniou.mld' '-I' '.' '-o' './page-biniou.odoc' '--child' 'module-Bi_dump' '--child' 'module-Bi_inbuf' '--child' 'module-Bi_io' '--child' 'module-Bi_outbuf' '--child' 'module-Bi_share' '--child' 'module-Bi_stream' '--child' 'module-Bi_util' '--child' 'module-Bi_vint' '--parent' 'page-"deps"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_xref_test.mld' '-I' '.' '-o' './page-odoc_xref_test.odoc' '--child' 'module-Odoc_xref_test' '--child' 'module-Odoc_xref_test__Common' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_xref2.mld' '-I' '.' '-o' './page-odoc_xref2.odoc' '--child' 'module-Odoc_xref2' '--child' 'module-Odoc_xref2__Cfrag' '--child' 'module-Odoc_xref2__Compile' '--child' 'module-Odoc_xref2__Component' '--child' 'module-Odoc_xref2__Cpath' '--child' 'module-Odoc_xref2__Env' '--child' 'module-Odoc_xref2__Errors' '--child' 'module-Odoc_xref2__Expand_tools' '--child' 'module-Odoc_xref2__Find' '--child' 'module-Odoc_xref2__Ident' '--child' 'module-Odoc_xref2__Lang_of' '--child' 'module-Odoc_xref2__Link' '--child' 'module-Odoc_xref2__Lookup_failures' '--child' 'module-Odoc_xref2__Ref_tools' '--child' 'module-Odoc_xref2__Strengthen' '--child' 'module-Odoc_xref2__Subst' '--child' 'module-Odoc_xref2__Tools' '--child' 'module-Odoc_xref2__Type_of' '--child' 'module-Odoc_xref2__Utils' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_odoc.mld' '-I' '.' '-o' './page-odoc_odoc.odoc' '--child' 'module-Odoc_odoc' '--child' 'module-Odoc_odoc__Compile' '--child' 'module-Odoc_odoc__Depends' '--child' 'module-Odoc_odoc__Fs' '--child' 'module-Odoc_odoc__Html_fragment' '--child' 'module-Odoc_odoc__Html_page' '--child' 'module-Odoc_odoc__Latex' '--child' 'module-Odoc_odoc__Man_page' '--child' 'module-Odoc_odoc__Odoc_file' '--child' 'module-Odoc_odoc__Odoc_link' '--child' 'module-Odoc_odoc__Or_error' '--child' 'module-Odoc_odoc__Rendering' '--child' 'module-Odoc_odoc__Resolver' '--child' 'module-Odoc_odoc__Source_tree' '--child' 'module-Odoc_odoc__Support_files' '--child' 'module-Odoc_odoc__Url' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_html_support_files.mld' '-I' '.' '-o' './page-odoc_html_support_files.odoc' '--child' 'module-Odoc_html_support_files' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_model_desc.mld' '-I' '.' '-o' './page-odoc_model_desc.odoc' '--child' 'module-Odoc_model_desc' '--child' 'module-Odoc_model_desc__Comment_desc' '--child' 'module-Odoc_model_desc__Lang_desc' '--child' 'module-Odoc_model_desc__Paths_desc' '--child' 'module-Odoc_model_desc__Type_desc' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_model.mld' '-I' '.' '-o' './page-odoc_model.odoc' '--child' 'module-Odoc_model' '--child' 'module-Odoc_model__' '--child' 'module-Odoc_model__Comment' '--child' 'module-Odoc_model__Compat' '--child' 'module-Odoc_model__Error' '--child' 'module-Odoc_model__Lang' '--child' 'module-Odoc_model__Location_' '--child' 'module-Odoc_model__Names' '--child' 'module-Odoc_model__Paths' '--child' 'module-Odoc_model__Paths_types' '--child' 'module-Odoc_model__Predefined' '--child' 'module-Odoc_model__Reference' '--child' 'module-Odoc_model__Root' '--child' 'module-Odoc_model__Semantics' '--child' 'module-Odoc_model_desc' '--child' 'module-Odoc_model_desc__Comment_desc' '--child' 'module-Odoc_model_desc__Lang_desc' '--child' 'module-Odoc_model_desc__Paths_desc' '--child' 'module-Odoc_model_desc__Type_desc' '--child' 'module-Odoc_model_semantics_test' '--child' 'module-Odoc_model_semantics_test__Test' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_manpage.mld' '-I' '.' '-o' './page-odoc_manpage.odoc' '--child' 'module-Odoc_manpage' '--child' 'module-Odoc_manpage__Generator' '--child' 'module-Odoc_manpage__Link' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_loader.mld' '-I' '.' '-o' './page-odoc_loader.odoc' '--child' 'module-Odoc_loader' '--child' 'module-Odoc_loader__' '--child' 'module-Odoc_loader__Cmi' '--child' 'module-Odoc_loader__Cmt' '--child' 'module-Odoc_loader__Cmti' '--child' 'module-Odoc_loader__Doc_attr' '--child' 'module-Odoc_loader__Ident_env' '--child' 'module-Odoc_loader__Local_jmp' '--child' 'module-Odoc_loader__Lookup_def' '--child' 'module-Odoc_loader__Source_info' '--child' 'module-Odoc_loader__Uid' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_latex.mld' '-I' '.' '-o' './page-odoc_latex.odoc' '--child' 'module-Odoc_latex' '--child' 'module-Odoc_latex__Generator' '--child' 'module-Odoc_latex__Raw' '--child' 'module-Odoc_latex__Types' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_html.mld' '-I' '.' '-o' './page-odoc_html.odoc' '--child' 'module-Odoc_html' '--child' 'module-Odoc_html__' '--child' 'module-Odoc_html__Config' '--child' 'module-Odoc_html__Generator' '--child' 'module-Odoc_html__Html_fragment_json' '--child' 'module-Odoc_html__Html_page' '--child' 'module-Odoc_html__Html_source' '--child' 'module-Odoc_html__Link' '--child' 'module-Odoc_html__Types' '--child' 'module-Odoc_html__Utils' '--child' 'module-Odoc_html_support_files' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_document.mld' '-I' '.' '-o' './page-odoc_document.odoc' '--child' 'module-Odoc_document' '--child' 'module-Odoc_document__Codefmt' '--child' 'module-Odoc_document__Comment' '--child' 'module-Odoc_document__Compat' '--child' 'module-Odoc_document__Doctree' '--child' 'module-Odoc_document__Generator' '--child' 'module-Odoc_document__Generator_signatures' '--child' 'module-Odoc_document__ML' '--child' 'module-Odoc_document__Reason' '--child' 'module-Odoc_document__Renderer' '--child' 'module-Odoc_document__Targets' '--child' 'module-Odoc_document__Types' '--child' 'module-Odoc_document__Url' '--child' 'module-Odoc_document__Utils' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'compile' 'library_mlds/odoc_examples.mld' '-I' '.' '-o' './page-odoc_examples.odoc' '--child' 'module-Odoc_examples' '--child' 'module-Odoc_examples__' '--child' 'module-Odoc_examples__Expansion' '--child' 'module-Odoc_examples__Markup' '--child' 'module-Odoc_examples__Resolution' '--child' 'module-Odoc_examples__Unexposed' '--child' 'module-Odoc_examples__Wrapping' '--parent' 'page-"odoc"' +$ '../src/odoc/bin/main.exe' 'source-tree' '-I' '.' '--parent' 'page-"odoc"' '-o' 'src-source.odoc' 'source.map' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../test/xref2/lib/.odoc_xref_test.objs/byte/odoc_xref_test__Common.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/warnings.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalFormatBasics.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalFormatBasics.cmti' '-I' '.' '-o' './camlinternalFormatBasics.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalLazy.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib.cmti' '-I' '.' '-o' './stdlib.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalLazy.cmti' '-I' '.' '-o' './camlinternalLazy.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Lazy.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Lazy.cmti' '-I' '.' '-o' './stdlib__Lazy.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Lexing.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Lexing.cmti' '-I' '.' '-o' './stdlib__Lexing.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Sys.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Sys.cmti' '-I' '.' '-o' './stdlib__Sys.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/warnings.cmti' '-I' '.' '-o' './warnings.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/types.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asttypes.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/location.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Buffer.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Either.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Either.cmti' '-I' '.' '-o' './stdlib__Either.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Seq.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Seq.cmti' '-I' '.' '-o' './stdlib__Seq.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Uchar.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Uchar.cmti' '-I' '.' '-o' './stdlib__Uchar.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Buffer.cmti' '-I' '.' '-o' './stdlib__Buffer.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Domain.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Domain.cmti' '-I' '.' '-o' './stdlib__Domain.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Format.cmti' '-I' '.' '-o' './stdlib__Format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/location.cmti' '-I' '.' '-o' './location.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asttypes.cmti' '-I' '.' '-o' './asttypes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ident.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/identifiable.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Hashtbl.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Hashtbl.cmti' '-I' '.' '-o' './stdlib__Hashtbl.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Map.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Map.cmti' '-I' '.' '-o' './stdlib__Map.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Set.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Set.cmti' '-I' '.' '-o' './stdlib__Set.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/identifiable.cmti' '-I' '.' '-o' './identifiable.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ident.cmti' '-I' '.' '-o' './ident.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/longident.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/longident.cmti' '-I' '.' '-o' './longident.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/outcometree.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parsetree.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parsetree.cmti' '-I' '.' '-o' './parsetree.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/type_immediacy.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/type_immediacy.cmti' '-I' '.' '-o' './type_immediacy.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/outcometree.cmti' '-I' '.' '-o' './outcometree.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/path.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/path.cmti' '-I' '.' '-o' './path.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/primitive.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/primitive.cmti' '-I' '.' '-o' './primitive.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/shape.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/shape.cmti' '-I' '.' '-o' './shape.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/types.cmti' '-I' '.' '-o' './types.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typemod.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/btype.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/btype.cmti' '-I' '.' '-o' './btype.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/build_path_prefix_map.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/build_path_prefix_map.cmti' '-I' '.' '-o' './build_path_prefix_map.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmi_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/misc.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Digest.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Digest.cmti' '-I' '.' '-o' './stdlib__Digest.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__String.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__String.cmti' '-I' '.' '-o' './stdlib__String.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/misc.cmti' '-I' '.' '-o' './misc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmi_format.cmti' '-I' '.' '-o' './cmi_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ctype.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/env.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/load_path.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/load_path.cmti' '-I' '.' '-o' './load_path.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/subst.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/subst.cmti' '-I' '.' '-o' './subst.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/env.cmti' '-I' '.' '-o' './env.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/errortrace.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/errortrace.cmti' '-I' '.' '-o' './errortrace.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ctype.cmti' '-I' '.' '-o' './ctype.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/diffing.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/diffing.cmti' '-I' '.' '-o' './diffing.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/diffing_with_keys.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/diffing_with_keys.cmti' '-I' '.' '-o' './diffing_with_keys.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/includecore.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedtree.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedtree.cmti' '-I' '.' '-o' './typedtree.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/includecore.cmti' '-I' '.' '-o' './includecore.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/includemod.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/includemod.cmti' '-I' '.' '-o' './includemod.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_immediacy.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_properties.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_properties.cmti' '-I' '.' '-o' './typedecl_properties.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_immediacy.cmti' '-I' '.' '-o' './typedecl_immediacy.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_separability.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_separability.cmti' '-I' '.' '-o' './typedecl_separability.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_variance.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_variance.cmti' '-I' '.' '-o' './typedecl_variance.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl.cmti' '-I' '.' '-o' './typedecl.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typemod.cmti' '-I' '.' '-o' './typemod.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/toploop.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Int32.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Int32.cmti' '-I' '.' '-o' './stdlib__Int32.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Obj.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Obj.cmti' '-I' '.' '-o' './stdlib__Obj.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/toploop.cmti' '-I' '.' '-o' './toploop.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Result.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Result.cmti' '-I' '.' '-o' './stdlib__Result.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Printf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Printf.cmti' '-I' '.' '-o' './stdlib__Printf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__List.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__List.cmti' '-I' '.' '-o' './stdlib__List.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Array.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Array.cmti' '-I' '.' '-o' './stdlib__Array.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Arg.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Arg.cmti' '-I' '.' '-o' './stdlib__Arg.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/result/result.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/result/result.cmt' '-I' '.' '-o' './result.odoc' '--parent' 'page-"result"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/profile.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/profile.cmti' '-I' '.' '-o' './profile.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parse.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parse.cmti' '-I' '.' '-o' './parse.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../test/xref2/lib/.odoc_xref_test.objs/byte/odoc_xref_test.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../test/xref2/lib/.odoc_xref_test.objs/byte/odoc_xref_test.cmt' '-I' '.' '-o' './odoc_xref_test.odoc' '--parent' 'page-"odoc_xref_test"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Tools.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/astring/astring.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/astring/astring.cmti' '-I' '.' '-o' './astring.odoc' '--parent' 'page-"astring"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__.cmt' '-I' '.' '-o' './odoc_model__.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model.cmt' '--source-name' 'src/model/odoc_model.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Comment.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Warning.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Loc.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__.cmt' '-I' '.' '-o' './odoc_parser__.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Loc.cmti' '-I' '.' '-o' './odoc_parser__Loc.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Warning.cmt' '-I' '.' '-o' './odoc_parser__Warning.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Ast.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Ast.cmt' '-I' '.' '-o' './odoc_parser__Ast.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser.cmti' '-I' '.' '-o' './odoc_parser.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Paths_types.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Names.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Names.cmti' '--source-name' 'src/model/names.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Names.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Paths_types.cmt' '--source-name' 'src/model/paths_types.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Paths_types.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Paths.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Paths.cmti' '--source-name' 'src/model/paths.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Paths.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Location_.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Location_.cmti' '--source-name' 'src/model/location_.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Location_.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Comment.cmt' '--source-name' 'src/model/comment.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Comment.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Error.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Error.cmti' '--source-name' 'src/model/error.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Error.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Lang.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Root.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Root.cmti' '--source-name' 'src/model/root.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Root.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Lang.cmt' '--source-name' 'src/model/lang.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Lang.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2.cmt' '-I' '.' '-o' './odoc_xref2.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Cfrag.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Ident.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Ident.cmt' '--source-name' 'src/xref2/ident.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Ident.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Cpath.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Cpath.cmt' '--source-name' 'src/xref2/cpath.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Cpath.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Cfrag.cmt' '--source-name' 'src/xref2/cfrag.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Cfrag.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Component.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Component.cmti' '--source-name' 'src/xref2/component.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Component.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Env.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Env.cmti' '--source-name' 'src/xref2/env.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Env.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Errors.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Lookup_failures.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Lookup_failures.cmti' '--source-name' 'src/xref2/lookup_failures.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Lookup_failures.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Errors.cmt' '--source-name' 'src/xref2/errors.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Errors.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Find.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Find.cmti' '--source-name' 'src/xref2/find.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Find.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Tools.cmti' '--source-name' 'src/xref2/tools.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Tools.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Compile.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Compile.cmti' '--source-name' 'src/xref2/compile.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Compile.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Resolver.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmt_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmt_format.cmti' '-I' '.' '-o' './cmt_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/fpath/fpath.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/fpath/fpath.cmti' '-I' '.' '-o' './fpath.odoc' '--parent' 'page-"fpath"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__.cmt' '-I' '.' '-o' './odoc_loader__.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Lookup_def.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Lookup_def.cmti' '--source-name' 'src/loader/lookup_def.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Lookup_def.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Source_info.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Source_info.cmti' '--source-name' 'src/loader/source_info.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Source_info.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader.cmti' '--source-name' 'src/loader/odoc_loader.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc.cmt' '-I' '.' '-o' './odoc_odoc.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Fs.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Or_error.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Or_error.cmti' '--source-name' 'src/odoc/or_error.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Or_error.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Fs.cmti' '--source-name' 'src/odoc/fs.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Fs.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Resolver.cmti' '--source-name' 'src/odoc/resolver.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Resolver.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Compat.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Compat.cmt' '--source-name' 'src/model/compat.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Compat.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Ident_env.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Ident_env.cmti' '--source-name' 'src/loader/ident_env.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Ident_env.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmti.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmti.cmti' '--source-name' 'src/loader/cmti.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Cmti.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmt.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmt.cmti' '--source-name' 'src/loader/cmt.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Cmt.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compmisc.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/clflags.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/clflags.cmti' '-I' '.' '-o' './clflags.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compmisc.cmti' '-I' '.' '-o' './compmisc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../test/xref2/lib/.odoc_xref_test.objs/byte/odoc_xref_test__Common.cmt' '-I' '.' '-o' './odoc_xref_test__Common.odoc' '--parent' 'page-"odoc_xref_test"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Utils.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Utils.cmt' '--source-name' 'src/xref2/utils.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Utils.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Type_of.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Type_of.cmti' '--source-name' 'src/xref2/type_of.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Type_of.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Subst.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Subst.cmti' '--source-name' 'src/xref2/subst.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Subst.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Strengthen.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Strengthen.cmt' '--source-name' 'src/xref2/strengthen.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Strengthen.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Ref_tools.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Ref_tools.cmti' '--source-name' 'src/xref2/ref_tools.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Ref_tools.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Link.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Link.cmti' '--source-name' 'src/xref2/link.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Link.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Lang_of.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Lang_of.cmti' '--source-name' 'src/xref2/lang_of.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Lang_of.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Expand_tools.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/xref2/.odoc_xref2.objs/byte/odoc_xref2__Expand_tools.cmt' '--source-name' 'src/xref2/expand_tools.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_xref2__Expand_tools.odoc' '--parent' 'page-"odoc_xref2"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Url.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_wrap.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_wrap.cmti' '-I' '.' '-o' './xml_wrap.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_stream.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_sigs.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_sigs.cmti' '-I' '.' '-o' './xml_sigs.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_stream.cmti' '-I' '.' '-o' './xml_stream.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/tyxml_xml.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/tyxml_xml.cmti' '-I' '.' '-o' './tyxml_xml.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/tyxml_svg.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/svg_sigs.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/svg_types.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/svg_types.cmti' '-I' '.' '-o' './svg_types.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/svg_sigs.cmti' '-I' '.' '-o' './svg_sigs.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/tyxml_svg.cmti' '-I' '.' '-o' './tyxml_svg.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/tyxml_html.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/html_sigs.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/html_types.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/html_types.cmti' '-I' '.' '-o' './html_types.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/html_sigs.cmti' '-I' '.' '-o' './html_sigs.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/tyxml_html.cmti' '-I' '.' '-o' './tyxml_html.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/tyxml.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/tyxml.cmt' '-I' '.' '-o' './tyxml.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Html_page.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document.cmt' '-I' '.' '-o' './odoc_document.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__ML.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Types.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Url.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Url.cmti' '--source-name' 'src/document/url.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Url.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Types.cmt' '--source-name' 'src/document/types.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Types.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__ML.cmti' '--source-name' 'src/document/ML.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__ML.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Reason.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Reason.cmti' '--source-name' 'src/document/reason.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Reason.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Renderer.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Renderer.cmt' '--source-name' 'src/document/renderer.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Renderer.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__.cmt' '-I' '.' '-o' './odoc_html__.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html.cmt' '--source-name' 'src/html/odoc_html.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Config.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Types.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Types.cmt' '--source-name' 'src/html/types.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Types.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Config.cmti' '--source-name' 'src/html/config.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Config.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Html_page.cmti' '--source-name' 'src/odoc/html_page.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Html_page.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Semantics.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Semantics.cmti' '--source-name' 'src/model/semantics.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Semantics.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Generator.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/latex/.odoc_latex.objs/byte/odoc_latex.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/latex/.odoc_latex.objs/byte/odoc_latex.cmt' '-I' '.' '-o' './odoc_latex.odoc' '--parent' 'page-"odoc_latex"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Generator.cmti' '--source-name' 'src/latex/generator.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_latex__Generator.odoc' '--parent' 'page-"odoc_latex"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Link.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Link.cmti' '--source-name' 'src/html/link.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Link.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Url.cmt' '--source-name' 'src/odoc/url.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Url.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Support_files.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Support_files.cmti' '--source-name' 'src/odoc/support_files.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Support_files.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Source_tree.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Source_tree.cmti' '--source-name' 'src/odoc/source_tree.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Source_tree.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Rendering.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Rendering.cmti' '--source-name' 'src/odoc/rendering.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Rendering.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Odoc_link.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Odoc_file.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Odoc_file.cmti' '--source-name' 'src/odoc/odoc_file.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Odoc_file.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Odoc_link.cmt' '--source-name' 'src/odoc/odoc_link.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Odoc_link.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Man_page.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage__Generator.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage.cmt' '-I' '.' '-o' './odoc_manpage.odoc' '--parent' 'page-"odoc_manpage"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage__Generator.cmti' '--source-name' 'src/manpage/generator.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_manpage__Generator.odoc' '--parent' 'page-"odoc_manpage"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Man_page.cmt' '--source-name' 'src/odoc/man_page.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Man_page.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Latex.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Latex.cmt' '--source-name' 'src/odoc/latex.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Latex.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Html_fragment.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Html_fragment.cmti' '--source-name' 'src/odoc/html_fragment.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Html_fragment.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Depends.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Depends.cmti' '--source-name' 'src/odoc/depends.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Depends.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Compile.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/odoc/.odoc_odoc.objs/byte/odoc_odoc__Compile.cmti' '--source-name' 'src/odoc/compile.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_odoc__Compile.odoc' '--parent' 'page-"odoc_odoc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html_support_files/.odoc_html_support_files.objs/byte/odoc_html_support_files.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html_support_files/.odoc_html_support_files.objs/byte/odoc_html_support_files.cmt' '--source-name' 'src/html_support_files/odoc_html_support_files.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html_support_files.odoc' '--parent' 'page-"odoc_html_support_files"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Type_desc.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc.cmt' '-I' '.' '-o' './odoc_model_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Type_desc.cmt' '--source-name' 'src/model_desc/type_desc.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model_desc__Type_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Paths_desc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Paths_desc.cmti' '--source-name' 'src/model_desc/paths_desc.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model_desc__Paths_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Lang_desc.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Comment_desc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Comment_desc.cmti' '--source-name' 'src/model_desc/comment_desc.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model_desc__Comment_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model_desc/.odoc_model_desc.objs/byte/odoc_model_desc__Lang_desc.cmt' '--source-name' 'src/model_desc/lang_desc.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model_desc__Lang_desc.odoc' '--parent' 'page-"odoc_model_desc"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../test/model/semantics/.odoc_model_semantics_test.objs/byte/odoc_model_semantics_test__Test.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/yojson/yojson.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_outbuf.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_share.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_share.cmti' '-I' '.' '-o' './bi_share.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_outbuf.cmti' '-I' '.' '-o' './bi_outbuf.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/yojson/yojson.cmti' '-I' '.' '-o' './yojson.odoc' '--parent' 'page-"yojson"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__StringLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__StringLabels.cmti' '-I' '.' '-o' './stdlib__StringLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__StdLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__StdLabels.cmti' '-I' '.' '-o' './stdlib__StdLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Printexc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Printexc.cmti' '-I' '.' '-o' './stdlib__Printexc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Nativeint.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Nativeint.cmti' '-I' '.' '-o' './stdlib__Nativeint.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__MoreLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__MoreLabels.cmti' '-I' '.' '-o' './stdlib__MoreLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__ListLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__ListLabels.cmti' '-I' '.' '-o' './stdlib__ListLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Int64.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Int64.cmti' '-I' '.' '-o' './stdlib__Int64.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__BytesLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__BytesLabels.cmti' '-I' '.' '-o' './stdlib__BytesLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../test/model/semantics/.odoc_model_semantics_test.objs/byte/odoc_model_semantics_test.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../test/model/semantics/.odoc_model_semantics_test.objs/byte/odoc_model_semantics_test.cmt' '-I' '.' '-o' './odoc_model_semantics_test.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile' '../test/model/semantics/.odoc_model_semantics_test.objs/byte/odoc_model_semantics_test__Test.cmt' '-I' '.' '-o' './odoc_model_semantics_test__Test.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Reference.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Reference.cmti' '--source-name' 'src/model/reference.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Reference.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/model/.odoc_model.objs/byte/odoc_model__Predefined.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/model/.odoc_model.objs/byte/odoc_model__Predefined.cmti' '--source-name' 'src/model/predefined.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_model__Predefined.odoc' '--parent' 'page-"odoc_model"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage__Link.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/manpage/.odoc_manpage.objs/byte/odoc_manpage__Link.cmt' '--source-name' 'src/manpage/link.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_manpage__Link.odoc' '--parent' 'page-"odoc_manpage"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Uid.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Uid.cmti' '--source-name' 'src/loader/uid.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Uid.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Local_jmp.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Local_jmp.cmti' '--source-name' 'src/loader/local_jmp.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Local_jmp.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Doc_attr.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Doc_attr.cmti' '--source-name' 'src/loader/doc_attr.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Doc_attr.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmi.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/loader/.odoc_loader.objs/byte/odoc_loader__Cmi.cmti' '--source-name' 'src/loader/cmi.pp.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_loader__Cmi.odoc' '--parent' 'page-"odoc_loader"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Types.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Types.cmt' '--source-name' 'src/latex/types.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_latex__Types.odoc' '--parent' 'page-"odoc_latex"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Raw.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/fmt/fmt.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Queue.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Queue.cmti' '-I' '.' '-o' './stdlib__Queue.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Stack.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Stack.cmti' '-I' '.' '-o' './stdlib__Stack.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/fmt/fmt.cmti' '-I' '.' '-o' './fmt.odoc' '--parent' 'page-"fmt"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/latex/.odoc_latex.objs/byte/odoc_latex__Raw.cmti' '--source-name' 'src/latex/raw.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_latex__Raw.odoc' '--parent' 'page-"odoc_latex"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Utils.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Char.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Char.cmti' '-I' '.' '-o' './stdlib__Char.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Utils.cmt' '--source-name' 'src/html/utils.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Utils.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Html_source.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Html_source.cmti' '--source-name' 'src/html/html_source.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Html_source.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Html_page.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Html_page.cmti' '--source-name' 'src/html/html_page.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Html_page.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Html_fragment_json.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Html_fragment_json.cmti' '--source-name' 'src/html/html_fragment_json.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Html_fragment_json.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/html/.odoc_html.objs/byte/odoc_html__Generator.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/html/.odoc_html.objs/byte/odoc_html__Generator.cmti' '--source-name' 'src/html/generator.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_html__Generator.odoc' '--parent' 'page-"odoc_html"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Utils.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Utils.cmti' '--source-name' 'src/document/utils.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Utils.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Targets.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Targets.cmti' '--source-name' 'src/document/targets.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Targets.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Generator_signatures.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Codefmt.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Codefmt.cmti' '--source-name' 'src/document/codefmt.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Codefmt.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Generator_signatures.cmt' '--source-name' 'src/document/generator_signatures.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Generator_signatures.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Generator.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Generator.cmti' '--source-name' 'src/document/generator.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Generator.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Doctree.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Doctree.cmt' '--source-name' 'src/document/doctree.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Doctree.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Compat.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Compat.cmt' '--source-name' 'src/document/compat.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Compat.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../src/document/.odoc_document.objs/byte/odoc_document__Comment.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../src/document/.odoc_document.objs/byte/odoc_document__Comment.cmt' '--source-name' 'src/document/comment.ml' '--source-parent-file' 'src-source.odoc' '-I' '.' '-o' './odoc_document__Comment.odoc' '--parent' 'page-"odoc_document"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Wrapping.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__.cmt' '-I' '.' '-o' './odoc_examples__.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Unexposed.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Unexposed.cmti' '-I' '.' '-o' './odoc_examples__Unexposed.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Wrapping.cmti' '-I' '.' '-o' './odoc_examples__Wrapping.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Resolution.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Resolution.cmti' '-I' '.' '-o' './odoc_examples__Resolution.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Markup.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Markup.cmti' '-I' '.' '-o' './odoc_examples__Markup.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Expansion.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples__Expansion.cmti' '-I' '.' '-o' './odoc_examples__Expansion.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../doc/examples/.odoc_examples.objs/byte/odoc_examples.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../doc/examples/.odoc_examples.objs/byte/odoc_examples.cmt' '-I' '.' '-o' './odoc_examples.odoc' '--parent' 'page-"odoc_examples"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Token.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Token.cmt' '-I' '.' '-o' './odoc_parser__Token.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Syntax.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Syntax.cmti' '-I' '.' '-o' './odoc_parser__Syntax.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Parse_error.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Parse_error.cmt' '-I' '.' '-o' './odoc_parser__Parse_error.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/odoc-parser/odoc_parser__Lexer.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/odoc-parser/odoc_parser__Lexer.cmti' '-I' '.' '-o' './odoc_parser__Lexer.odoc' '--parent' 'page-"odoc-parser"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/cmdliner/cmdliner.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/cmdliner/cmdliner.cmti' '-I' '.' '-o' './cmdliner.odoc' '--parent' 'page-"cmdliner"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_print.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_print.cmti' '-I' '.' '-o' './xml_print.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/xml_iter.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/xml_iter.cmti' '-I' '.' '-o' './xml_iter.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/svg_f.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/svg_f.cmti' '-I' '.' '-o' './svg_f.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/tyxml/functor/html_f.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/tyxml/functor/html_f.cmti' '-I' '.' '-o' './html_f.odoc' '--parent' 'page-"tyxml"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/fmt/fmt_tty.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/fmt/fmt_tty.cmti' '-I' '.' '-o' './fmt_tty.odoc' '--parent' 'page-"fmt"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/fmt/fmt_cli.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/fmt/fmt_cli.cmti' '-I' '.' '-o' './fmt_cli.odoc' '--parent' 'page-"fmt"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/unix/unixLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Bigarray.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Complex.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Complex.cmti' '-I' '.' '-o' './stdlib__Complex.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Bigarray.cmti' '-I' '.' '-o' './stdlib__Bigarray.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/unix/unix.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/unix/unix.cmti' '-I' '.' '-o' './unix.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/unix/unixLabels.cmti' '-I' '.' '-o' './unixLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/threads/thread.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/threads/thread.cmti' '-I' '.' '-o' './thread.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/threads/event.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/threads/event.cmti' '-I' '.' '-o' './event.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/str/str.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/str/str.cmti' '-I' '.' '-o' './str.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Weak.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Weak.cmti' '-I' '.' '-o' './stdlib__Weak.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Unit.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Unit.cmti' '-I' '.' '-o' './stdlib__Unit.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Semaphore.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Semaphore.cmti' '-I' '.' '-o' './stdlib__Semaphore.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Scanf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Scanf.cmti' '-I' '.' '-o' './stdlib__Scanf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Random.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Random.cmti' '-I' '.' '-o' './stdlib__Random.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Parsing.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Parsing.cmti' '-I' '.' '-o' './stdlib__Parsing.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Out_channel.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Out_channel.cmti' '-I' '.' '-o' './stdlib__Out_channel.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Option.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Option.cmti' '-I' '.' '-o' './stdlib__Option.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Oo.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalOO.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalOO.cmti' '-I' '.' '-o' './camlinternalOO.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Oo.cmti' '-I' '.' '-o' './stdlib__Oo.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Mutex.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Mutex.cmti' '-I' '.' '-o' './stdlib__Mutex.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Marshal.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Marshal.cmti' '-I' '.' '-o' './stdlib__Marshal.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Int.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Int.cmti' '-I' '.' '-o' './stdlib__Int.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__In_channel.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__In_channel.cmti' '-I' '.' '-o' './stdlib__In_channel.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Gc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Gc.cmti' '-I' '.' '-o' './stdlib__Gc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Fun.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Fun.cmti' '-I' '.' '-o' './stdlib__Fun.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Float.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Float.cmti' '-I' '.' '-o' './stdlib__Float.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Filename.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Filename.cmti' '-I' '.' '-o' './stdlib__Filename.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Ephemeron.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Ephemeron.cmti' '-I' '.' '-o' './stdlib__Ephemeron.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Effect.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Effect.cmti' '-I' '.' '-o' './stdlib__Effect.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Condition.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Condition.cmti' '-I' '.' '-o' './stdlib__Condition.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Callback.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Callback.cmti' '-I' '.' '-o' './stdlib__Callback.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Bytes.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Bytes.cmti' '-I' '.' '-o' './stdlib__Bytes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Bool.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Bool.cmti' '-I' '.' '-o' './stdlib__Bool.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__Atomic.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__Atomic.cmti' '-I' '.' '-o' './stdlib__Atomic.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/stdlib__ArrayLabels.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/stdlib__ArrayLabels.cmti' '-I' '.' '-o' './stdlib__ArrayLabels.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/std_exit.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/std_exit.cmt' '-I' '.' '-o' './std_exit.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/runtime_events/runtime_events.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/runtime_events/runtime_events.cmti' '-I' '.' '-o' './runtime_events.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/profiling/profiling.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/profiling/profiling.cmti' '-I' '.' '-o' './profiling.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/ocamlmktop/ocamlmktop_init.cmi' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/genprintval.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/genprintval.cmti' '-I' '.' '-o' './genprintval.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topcommon.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topcommon.cmti' '-I' '.' '-o' './topcommon.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/ocamlmktop/ocamlmktop_init.cmi' '-I' '.' '-o' './ocamlmktop_init.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/dynlink/dynlink.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/dynlink/dynlink.cmti' '-I' '.' '-o' './dynlink.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_proc.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_ast.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_ast.cmti' '-I' '.' '-o' './x86_ast.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_proc.cmti' '-I' '.' '-o' './x86_proc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_masm.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_masm.cmti' '-I' '.' '-o' './x86_masm.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_gas.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_gas.cmti' '-I' '.' '-o' './x86_gas.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/x86_dsl.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/x86_dsl.cmti' '-I' '.' '-o' './x86_dsl.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/variable.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compilation_unit.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linkage_name.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linkage_name.cmti' '-I' '.' '-o' './linkage_name.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compilation_unit.cmti' '-I' '.' '-o' './compilation_unit.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/debuginfo.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/debuginfo.cmti' '-I' '.' '-o' './debuginfo.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/internal_variable_names.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lambda.cmti' '-I' '.' '-o' './lambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/internal_variable_names.cmti' '-I' '.' '-o' './internal_variable_names.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/variable.cmti' '-I' '.' '-o' './variable.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/var_within_closure.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_element.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_element.cmti' '-I' '.' '-o' './closure_element.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/var_within_closure.cmti' '-I' '.' '-o' './var_within_closure.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/untypeast.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/untypeast.cmti' '-I' '.' '-o' './untypeast.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/unbox_specialised_args.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/allocated_const.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/allocated_const.cmti' '-I' '.' '-o' './allocated_const.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/backend_intf.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/clambda_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/clambda_primitives.cmti' '-I' '.' '-o' './clambda_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_id.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_id.cmti' '-I' '.' '-o' './closure_id.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_origin.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_origin.cmti' '-I' '.' '-o' './closure_origin.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/export_id.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/export_id.cmti' '-I' '.' '-o' './export_id.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/mutable_variable.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/mutable_variable.cmti' '-I' '.' '-o' './mutable_variable.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/numbers.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/numbers.cmti' '-I' '.' '-o' './numbers.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parameter.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parameter.cmti' '-I' '.' '-o' './parameter.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/projection.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/projection.cmti' '-I' '.' '-o' './projection.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/set_of_closures_id.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/set_of_closures_id.cmti' '-I' '.' '-o' './set_of_closures_id.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/set_of_closures_origin.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/set_of_closures_origin.cmti' '-I' '.' '-o' './set_of_closures_origin.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/static_exception.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/static_exception.cmti' '-I' '.' '-o' './static_exception.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/symbol.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/symbol.cmti' '-I' '.' '-o' './symbol.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tag.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tag.cmti' '-I' '.' '-o' './tag.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda.cmti' '-I' '.' '-o' './flambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/freshening.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/freshening.cmti' '-I' '.' '-o' './freshening.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simple_value_approx.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simple_value_approx.cmti' '-I' '.' '-o' './simple_value_approx.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/backend_intf.cmti' '-I' '.' '-o' './backend_intf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inline_and_simplify_aux.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_cost.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_cost.cmti' '-I' '.' '-o' './inlining_cost.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_stats_types.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_stats_types.cmti' '-I' '.' '-o' './inlining_stats_types.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inline_and_simplify_aux.cmti' '-I' '.' '-o' './inline_and_simplify_aux.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/unbox_specialised_args.cmti' '-I' '.' '-o' './unbox_specialised_args.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/unbox_free_vars_of_closures.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/unbox_free_vars_of_closures.cmti' '-I' '.' '-o' './unbox_free_vars_of_closures.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/unbox_closures.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/unbox_closures.cmti' '-I' '.' '-o' './unbox_closures.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/un_anf.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/backend_var.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/backend_var.cmti' '-I' '.' '-o' './backend_var.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/clambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/clambda.cmti' '-I' '.' '-o' './clambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/un_anf.cmti' '-I' '.' '-o' './un_anf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typetexp.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typetexp.cmti' '-I' '.' '-o' './typetexp.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typeopt.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typeopt.cmti' '-I' '.' '-o' './typeopt.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typedecl_unboxed.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typedecl_unboxed.cmti' '-I' '.' '-o' './typedecl_unboxed.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typecore.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typecore.cmti' '-I' '.' '-o' './typecore.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/typeclass.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/typeclass.cmti' '-I' '.' '-o' './typeclass.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/traverse_for_exported_symbols.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/export_info.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/export_info.cmti' '-I' '.' '-o' './export_info.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/traverse_for_exported_symbols.cmti' '-I' '.' '-o' './traverse_for_exported_symbols.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translprim.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translprim.cmti' '-I' '.' '-o' './translprim.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translobj.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translobj.cmti' '-I' '.' '-o' './translobj.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translmod.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translmod.cmti' '-I' '.' '-o' './translmod.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translcore.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translcore.cmti' '-I' '.' '-o' './translcore.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translclass.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translclass.cmti' '-I' '.' '-o' './translclass.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/translattribute.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/translattribute.cmti' '-I' '.' '-o' './translattribute.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/trace.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/trace.cmti' '-I' '.' '-o' './trace.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topstart.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topmain.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topmain.cmti' '-I' '.' '-o' './topmain.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topstart.cmt' '-I' '.' '-o' './topstart.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tophooks.cmi' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tophooks.cmi' '-I' '.' '-o' './tophooks.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topeval.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topeval.cmti' '-I' '.' '-o' './topeval.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/topdirs.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/topdirs.cmti' '-I' '.' '-o' './topdirs.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tmc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tmc.cmti' '-I' '.' '-o' './tmc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/terminfo.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/terminfo.cmti' '-I' '.' '-o' './terminfo.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tast_mapper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tast_mapper.cmti' '-I' '.' '-o' './tast_mapper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/tast_iterator.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/tast_iterator.cmti' '-I' '.' '-o' './tast_iterator.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/targetint.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/targetint.cmti' '-I' '.' '-o' './targetint.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/syntaxerr.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/syntaxerr.cmti' '-I' '.' '-o' './syntaxerr.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/symtable.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmo_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmo_format.cmti' '-I' '.' '-o' './cmo_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/symtable.cmti' '-I' '.' '-o' './symtable.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/switch.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/switch.cmti' '-I' '.' '-o' './switch.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/stypes.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/annot.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/annot.cmti' '-I' '.' '-o' './annot.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/stypes.cmti' '-I' '.' '-o' './stypes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/strongly_connected_components.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/strongly_connected_components.cmti' '-I' '.' '-o' './strongly_connected_components.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/strmatch.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmm.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmm.cmti' '-I' '.' '-o' './cmm.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/strmatch.cmti' '-I' '.' '-o' './strmatch.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/split.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/arch.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/config.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/config.cmti' '-I' '.' '-o' './config.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/arch.cmt' '-I' '.' '-o' './arch.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/mach.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/reg.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/reg.cmti' '-I' '.' '-o' './reg.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/mach.cmti' '-I' '.' '-o' './mach.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/split.cmti' '-I' '.' '-o' './split.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/spill.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/spill.cmti' '-I' '.' '-o' './spill.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplify_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplify_primitives.cmti' '-I' '.' '-o' './simplify_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplify_common.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplify_common.cmti' '-I' '.' '-o' './simplify_common.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplify_boxed_integer_ops_intf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplify_boxed_integer_ops_intf.cmti' '-I' '.' '-o' './simplify_boxed_integer_ops_intf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplify_boxed_integer_ops.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplify_boxed_integer_ops.cmti' '-I' '.' '-o' './simplify_boxed_integer_ops.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/simplif.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/simplif.cmti' '-I' '.' '-o' './simplif.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/signature_group.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/signature_group.cmti' '-I' '.' '-o' './signature_group.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/share_constants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/share_constants.cmti' '-I' '.' '-o' './share_constants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/semantics_of_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/semantics_of_primitives.cmti' '-I' '.' '-o' './semantics_of_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/selection.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/selection.cmti' '-I' '.' '-o' './selection.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/selectgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/selectgen.cmti' '-I' '.' '-o' './selectgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/scheduling.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linear.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linear.cmti' '-I' '.' '-o' './linear.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/scheduling.cmti' '-I' '.' '-o' './scheduling.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/schedgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/schedgen.cmti' '-I' '.' '-o' './schedgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/runtimedef.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/runtimedef.cmti' '-I' '.' '-o' './runtimedef.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_program_constructs.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_program_constructs.cmti' '-I' '.' '-o' './remove_unused_program_constructs.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_closure_vars.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_closure_vars.cmti' '-I' '.' '-o' './remove_unused_closure_vars.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_arguments.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/remove_unused_arguments.cmti' '-I' '.' '-o' './remove_unused_arguments.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/remove_free_vars_equal_to_args.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/remove_free_vars_equal_to_args.cmti' '-I' '.' '-o' './remove_free_vars_equal_to_args.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/reloadgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/reloadgen.cmti' '-I' '.' '-o' './reloadgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/reload.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/reload.cmti' '-I' '.' '-o' './reload.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ref_to_variables.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ref_to_variables.cmti' '-I' '.' '-o' './ref_to_variables.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/rec_check.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/rec_check.cmti' '-I' '.' '-o' './rec_check.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/proc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/proc.cmti' '-I' '.' '-o' './proc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printtyped.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printtyped.cmti' '-I' '.' '-o' './printtyped.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printtyp.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printtyp.cmti' '-I' '.' '-o' './printtyp.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printpat.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printpat.cmti' '-I' '.' '-o' './printpat.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printmach.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printmach.cmti' '-I' '.' '-o' './printmach.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printlinear.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printlinear.cmti' '-I' '.' '-o' './printlinear.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printlambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printlambda.cmti' '-I' '.' '-o' './printlambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printinstr.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/instruct.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/instruct.cmti' '-I' '.' '-o' './instruct.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printinstr.cmti' '-I' '.' '-o' './printinstr.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printcmm.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printcmm.cmti' '-I' '.' '-o' './printcmm.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printclambda_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printclambda_primitives.cmti' '-I' '.' '-o' './printclambda_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printclambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printclambda.cmti' '-I' '.' '-o' './printclambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/printast.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/printast.cmti' '-I' '.' '-o' './printast.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/predef.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/predef.cmti' '-I' '.' '-o' './predef.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/pprintast.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/pprintast.cmti' '-I' '.' '-o' './pprintast.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/pparse.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/pparse.cmti' '-I' '.' '-o' './pparse.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/polling.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/polling.cmti' '-I' '.' '-o' './polling.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/persistent_env.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/consistbl.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/consistbl.cmti' '-I' '.' '-o' './consistbl.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lazy_backtrack.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lazy_backtrack.cmti' '-I' '.' '-o' './lazy_backtrack.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/persistent_env.cmti' '-I' '.' '-o' './persistent_env.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/patterns.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/patterns.cmti' '-I' '.' '-o' './patterns.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/pass_wrapper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/pass_wrapper.cmti' '-I' '.' '-o' './pass_wrapper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parser.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/camlinternalMenhirLib.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/camlinternalMenhirLib.cmti' '-I' '.' '-o' './camlinternalMenhirLib.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/docstrings.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/docstrings.cmti' '-I' '.' '-o' './docstrings.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parser.cmti' '-I' '.' '-o' './parser.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/parmatch.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/parmatch.cmti' '-I' '.' '-o' './parmatch.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/optmaindriver.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/optmaindriver.cmti' '-I' '.' '-o' './optmaindriver.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/optmain.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/optmain.cmt' '-I' '.' '-o' './optmain.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/opterrors.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/opterrors.cmti' '-I' '.' '-o' './opterrors.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/optcompile.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compile_common.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compile_common.cmti' '-I' '.' '-o' './compile_common.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/optcompile.cmti' '-I' '.' '-o' './optcompile.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/oprint.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/oprint.cmti' '-I' '.' '-o' './oprint.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/opcodes.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/opcodes.cmti' '-I' '.' '-o' './opcodes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/mtype.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/mtype.cmti' '-I' '.' '-o' './mtype.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/meta.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/meta.cmti' '-I' '.' '-o' './meta.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/matching.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/matching.cmti' '-I' '.' '-o' './matching.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/makedepend.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/makedepend.cmti' '-I' '.' '-o' './makedepend.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/maindriver.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/maindriver.cmti' '-I' '.' '-o' './maindriver.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/main_args.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/main_args.cmti' '-I' '.' '-o' './main_args.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/main.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/main.cmt' '-I' '.' '-o' './main.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/local_store.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/local_store.cmti' '-I' '.' '-o' './local_store.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/liveness.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/liveness.cmti' '-I' '.' '-o' './liveness.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linscan.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linscan.cmti' '-I' '.' '-o' './linscan.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linearize.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linearize.cmti' '-I' '.' '-o' './linearize.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/linear_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/linear_format.cmti' '-I' '.' '-o' './linear_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lift_let_to_initialize_symbol.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lift_let_to_initialize_symbol.cmti' '-I' '.' '-o' './lift_let_to_initialize_symbol.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lift_constants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lift_constants.cmti' '-I' '.' '-o' './lift_constants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lift_code.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lift_code.cmti' '-I' '.' '-o' './lift_code.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/lexer.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/lexer.cmti' '-I' '.' '-o' './lexer.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/invariant_params.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/invariant_params.cmti' '-I' '.' '-o' './invariant_params.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/interval.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/interval.cmti' '-I' '.' '-o' './interval.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/interf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/interf.cmti' '-I' '.' '-o' './interf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/int_replace_polymorphic_compare.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/int_replace_polymorphic_compare.cmti' '-I' '.' '-o' './int_replace_polymorphic_compare.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_transforms.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_decision_intf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_decision_intf.cmti' '-I' '.' '-o' './inlining_decision_intf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_transforms.cmti' '-I' '.' '-o' './inlining_transforms.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_stats.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_stats.cmti' '-I' '.' '-o' './inlining_stats.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inlining_decision.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inlining_decision.cmti' '-I' '.' '-o' './inlining_decision.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inline_and_simplify.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inline_and_simplify.cmti' '-I' '.' '-o' './inline_and_simplify.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/initialize_symbol_to_let_symbol.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/initialize_symbol_to_let_symbol.cmti' '-I' '.' '-o' './initialize_symbol_to_let_symbol.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/inconstant_idents.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/inconstant_idents.cmti' '-I' '.' '-o' './inconstant_idents.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/includemod_errorprinter.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/includemod_errorprinter.cmti' '-I' '.' '-o' './includemod_errorprinter.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/includeclass.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/includeclass.cmti' '-I' '.' '-o' './includeclass.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/import_approx.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/import_approx.cmti' '-I' '.' '-o' './import_approx.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/id_types.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/id_types.cmti' '-I' '.' '-o' './id_types.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_utils.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_utils.cmti' '-I' '.' '-o' './flambda_utils.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_to_clambda.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_to_clambda.cmti' '-I' '.' '-o' './flambda_to_clambda.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_middle_end.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_middle_end.cmti' '-I' '.' '-o' './flambda_middle_end.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_iterators.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_iterators.cmti' '-I' '.' '-o' './flambda_iterators.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/flambda_invariants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/flambda_invariants.cmti' '-I' '.' '-o' './flambda_invariants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/find_recursive_functions.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/find_recursive_functions.cmti' '-I' '.' '-o' './find_recursive_functions.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/extract_projections.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/extract_projections.cmti' '-I' '.' '-o' './extract_projections.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/expunge.cmt' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytesections.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytesections.cmti' '-I' '.' '-o' './bytesections.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/expunge.cmt' '-I' '.' '-o' './expunge.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/export_info_for_pack.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/export_info_for_pack.cmti' '-I' '.' '-o' './export_info_for_pack.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/errors.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/errors.cmti' '-I' '.' '-o' './errors.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/envaux.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/envaux.cmti' '-I' '.' '-o' './envaux.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/emitenv.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/emitenv.cmti' '-I' '.' '-o' './emitenv.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/emitcode.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/emitcode.cmti' '-I' '.' '-o' './emitcode.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/emitaux.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/emitaux.cmti' '-I' '.' '-o' './emitaux.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/emit.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/emit.cmti' '-I' '.' '-o' './emit.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/effect_analysis.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/effect_analysis.cmti' '-I' '.' '-o' './effect_analysis.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/domainstate.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/domainstate.cmti' '-I' '.' '-o' './domainstate.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/dll.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/dll.cmti' '-I' '.' '-o' './dll.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/depend.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/depend.cmti' '-I' '.' '-o' './depend.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/deadcode.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/deadcode.cmti' '-I' '.' '-o' './deadcode.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/datarepr.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/datarepr.cmti' '-I' '.' '-o' './datarepr.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/dataflow.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/dataflow.cmti' '-I' '.' '-o' './dataflow.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/convert_primitives.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/convert_primitives.cmti' '-I' '.' '-o' './convert_primitives.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/config_main.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/config_main.cmti' '-I' '.' '-o' './config_main.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/config_boot.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/config_boot.cmti' '-I' '.' '-o' './config_boot.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compilenv.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmx_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmx_format.cmti' '-I' '.' '-o' './cmx_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compilenv.cmti' '-I' '.' '-o' './compilenv.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compile.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compile.cmti' '-I' '.' '-o' './compile.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/compenv.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/compenv.cmti' '-I' '.' '-o' './compenv.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/comballoc.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/comballoc.cmti' '-I' '.' '-o' './comballoc.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/coloring.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/coloring.cmti' '-I' '.' '-o' './coloring.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmxs_format.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmxs_format.cmti' '-I' '.' '-o' './cmxs_format.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmt2annot.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmt2annot.cmt' '-I' '.' '-o' './cmt2annot.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmmgen_state.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmmgen_state.cmti' '-I' '.' '-o' './cmmgen_state.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmmgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmmgen.cmti' '-I' '.' '-o' './cmmgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmm_invariants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmm_invariants.cmti' '-I' '.' '-o' './cmm_invariants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/cmm_helpers.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/cmm_helpers.cmti' '-I' '.' '-o' './cmm_helpers.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_offsets.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_offsets.cmti' '-I' '.' '-o' './closure_offsets.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_middle_end.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_middle_end.cmti' '-I' '.' '-o' './closure_middle_end.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_conversion_aux.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_conversion_aux.cmti' '-I' '.' '-o' './closure_conversion_aux.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure_conversion.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure_conversion.cmti' '-I' '.' '-o' './closure_conversion.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/closure.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/closure.cmti' '-I' '.' '-o' './closure.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ccomp.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ccomp.cmti' '-I' '.' '-o' './ccomp.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytepackager.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytepackager.cmti' '-I' '.' '-o' './bytepackager.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytelink.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytelink.cmti' '-I' '.' '-o' './bytelink.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytelibrarian.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytelibrarian.cmti' '-I' '.' '-o' './bytelibrarian.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/bytegen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/bytegen.cmti' '-I' '.' '-o' './bytegen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/builtin_attributes.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/builtin_attributes.cmti' '-I' '.' '-o' './builtin_attributes.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/build_export_info.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/build_export_info.cmti' '-I' '.' '-o' './build_export_info.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/branch_relaxation_intf.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/branch_relaxation_intf.cmt' '-I' '.' '-o' './branch_relaxation_intf.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/branch_relaxation.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/branch_relaxation.cmti' '-I' '.' '-o' './branch_relaxation.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/binutils.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/binutils.cmti' '-I' '.' '-o' './binutils.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/augment_specialised_args.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/augment_specialised_args.cmti' '-I' '.' '-o' './augment_specialised_args.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/attr_helper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/attr_helper.cmti' '-I' '.' '-o' './attr_helper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ast_mapper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ast_mapper.cmti' '-I' '.' '-o' './ast_mapper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ast_iterator.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ast_iterator.cmti' '-I' '.' '-o' './ast_iterator.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ast_invariants.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ast_invariants.cmti' '-I' '.' '-o' './ast_invariants.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/ast_helper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/ast_helper.cmti' '-I' '.' '-o' './ast_helper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asmpackager.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asmpackager.cmti' '-I' '.' '-o' './asmpackager.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asmlink.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asmlink.cmti' '-I' '.' '-o' './asmlink.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asmlibrarian.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asmlibrarian.cmti' '-I' '.' '-o' './asmlibrarian.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/asmgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/asmgen.cmti' '-I' '.' '-o' './asmgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/arg_helper.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/arg_helper.cmti' '-I' '.' '-o' './arg_helper.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/alias_analysis.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/alias_analysis.cmti' '-I' '.' '-o' './alias_analysis.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/afl_instrument.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/afl_instrument.cmti' '-I' '.' '-o' './afl_instrument.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/CSEgen.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/CSEgen.cmti' '-I' '.' '-o' './CSEgen.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/compiler-libs/CSE.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/compiler-libs/CSE.cmt' '-I' '.' '-o' './CSE.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalMod.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalMod.cmti' '-I' '.' '-o' './camlinternalMod.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/ocaml/camlinternalFormat.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/ocaml/camlinternalFormat.cmti' '-I' '.' '-o' './camlinternalFormat.odoc' '--parent' 'page-"stdlib"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/yojson/yojson_biniou.cmti' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_inbuf.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_inbuf.cmti' '-I' '.' '-o' './bi_inbuf.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_io.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_io.cmti' '-I' '.' '-o' './bi_io.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/yojson/yojson_biniou.cmti' '-I' '.' '-o' './yojson_biniou.odoc' '--parent' 'page-"yojson"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_vint.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_vint.cmti' '-I' '.' '-o' './bi_vint.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_util.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_util.cmti' '-I' '.' '-o' './bi_util.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_stream.cmti' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_stream.cmti' '-I' '.' '-o' './bi_stream.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'compile-deps' '../../../_opam/lib/biniou/bi_dump.cmt' +$ '../src/odoc/bin/main.exe' 'compile' '../../../_opam/lib/biniou/bi_dump.cmt' '-I' '.' '-o' './bi_dump.odoc' '--parent' 'page-"biniou"' +$ '../src/odoc/bin/main.exe' 'link' 'src-source.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref_test__Common.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compmisc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'clflags.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Cmt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Cmti.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Ident_env.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Compat.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Resolver.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Fs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Or_error.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Source_info.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Lookup_def.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'fpath.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmt_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Compile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Tools.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Find.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Errors.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Lookup_failures.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Env.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Component.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Cfrag.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Cpath.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Ident.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Lang.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Root.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Error.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Comment.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Location_.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Paths.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Paths_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Names.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Ast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Warning.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Loc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'astring.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref_test.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parse.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'profile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'result.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Arg.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Array.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__List.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Printf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Result.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'toploop.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Obj.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Int32.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typemod.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_variance.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_separability.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_immediacy.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_properties.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'includemod.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'includecore.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedtree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'diffing_with_keys.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'diffing.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ctype.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'errortrace.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'env.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'subst.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'load_path.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmi_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'misc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__String.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Digest.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'build_path_prefix_map.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'btype.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'shape.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'primitive.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'path.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'outcometree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'type_immediacy.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parsetree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'longident.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ident.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'identifiable.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Set.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Map.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Hashtbl.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asttypes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'location.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Domain.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Buffer.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Uchar.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Seq.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Either.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'warnings.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Sys.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Lexing.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Lazy.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalLazy.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib.odoc' '-I' '.' '--open=""' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalFormatBasics.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Utils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Type_of.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Subst.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Strengthen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Ref_tools.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Link.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Lang_of.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_xref2__Expand_tools.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Url.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Link.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_latex__Generator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_latex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Semantics.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Html_page.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Config.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Renderer.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Reason.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__ML.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Url.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tyxml.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tyxml_html.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'html_sigs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'html_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tyxml_svg.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'svg_sigs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'svg_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tyxml_xml.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_stream.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_sigs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_wrap.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Support_files.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Source_tree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Rendering.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Odoc_link.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Odoc_file.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Man_page.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_manpage__Generator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_manpage.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Latex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Html_fragment.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Depends.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_odoc__Compile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html_support_files.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc__Type_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc__Paths_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc__Lang_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_desc__Comment_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_semantics_test__Test.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model_semantics_test.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__BytesLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Int64.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__ListLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__MoreLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Nativeint.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Printexc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__StdLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__StringLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'yojson.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_outbuf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_share.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Reference.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_model__Predefined.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_manpage__Link.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Uid.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Local_jmp.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Doc_attr.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_loader__Cmi.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_latex__Types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_latex__Raw.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'fmt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Stack.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Queue.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Utils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Char.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Html_source.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Html_page.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Html_fragment_json.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_html__Generator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Utils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Targets.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Generator_signatures.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Codefmt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Generator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Doctree.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Compat.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_document__Comment.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Wrapping.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Unexposed.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Resolution.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Markup.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples__Expansion.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_examples.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Token.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Syntax.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Parse_error.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'odoc_parser__Lexer.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmdliner.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_print.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'xml_iter.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'svg_f.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'html_f.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'fmt_tty.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'fmt_cli.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unixLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unix.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Bigarray.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Complex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'thread.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'event.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'str.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Weak.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Unit.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Semaphore.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Scanf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Random.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Parsing.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Out_channel.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Option.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Oo.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalOO.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Mutex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Marshal.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Int.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__In_channel.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Gc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Fun.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Float.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Filename.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Ephemeron.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Effect.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Condition.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Callback.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Bytes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Bool.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__Atomic.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stdlib__ArrayLabels.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'std_exit.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'runtime_events.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'profiling.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ocamlmktop_init.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topcommon.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'genprintval.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'dynlink.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_proc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_ast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_masm.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_gas.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'x86_dsl.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'variable.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'internal_variable_names.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'debuginfo.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compilation_unit.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linkage_name.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'var_within_closure.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_element.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'untypeast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unbox_specialised_args.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inline_and_simplify_aux.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_stats_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_cost.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'backend_intf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simple_value_approx.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'freshening.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tag.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'symbol.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'static_exception.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'set_of_closures_origin.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'set_of_closures_id.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'projection.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parameter.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'numbers.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'mutable_variable.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'export_id.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_origin.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_id.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'clambda_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'allocated_const.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unbox_free_vars_of_closures.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'unbox_closures.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'un_anf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'clambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'backend_var.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typetexp.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typeopt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typedecl_unboxed.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typecore.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'typeclass.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'traverse_for_exported_symbols.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'export_info.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translprim.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translobj.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translmod.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translcore.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translclass.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'translattribute.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'trace.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topstart.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topmain.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tophooks.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topeval.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'topdirs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tmc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'terminfo.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tast_mapper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'tast_iterator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'targetint.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'syntaxerr.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'symtable.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmo_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'switch.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'stypes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'annot.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'strongly_connected_components.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'strmatch.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmm.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'split.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'mach.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'reg.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'arch.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'config.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'spill.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplify_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplify_common.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplify_boxed_integer_ops_intf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplify_boxed_integer_ops.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'simplif.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'signature_group.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'share_constants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'semantics_of_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'selection.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'selectgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'scheduling.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linear.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'schedgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'runtimedef.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'remove_unused_program_constructs.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'remove_unused_closure_vars.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'remove_unused_arguments.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'remove_free_vars_equal_to_args.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'reloadgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'reload.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ref_to_variables.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'rec_check.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'proc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printtyped.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printtyp.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printpat.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printmach.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printlinear.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printlambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printinstr.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'instruct.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printcmm.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printclambda_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printclambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'printast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'predef.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'pprintast.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'pparse.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'polling.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'persistent_env.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lazy_backtrack.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'consistbl.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'patterns.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'pass_wrapper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parser.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'docstrings.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalMenhirLib.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'parmatch.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'optmaindriver.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'optmain.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'opterrors.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'optcompile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compile_common.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'oprint.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'opcodes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'mtype.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'meta.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'matching.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'makedepend.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'maindriver.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'main_args.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'main.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'local_store.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'liveness.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linscan.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linearize.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'linear_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lift_let_to_initialize_symbol.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lift_constants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lift_code.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'lexer.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'invariant_params.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'interval.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'interf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'int_replace_polymorphic_compare.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_transforms.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_decision_intf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_stats.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inlining_decision.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inline_and_simplify.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'initialize_symbol_to_let_symbol.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'inconstant_idents.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'includemod_errorprinter.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'includeclass.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'import_approx.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'id_types.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_utils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_to_clambda.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_middle_end.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_iterators.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'flambda_invariants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'find_recursive_functions.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'extract_projections.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'expunge.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytesections.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'export_info_for_pack.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'errors.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'envaux.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'emitenv.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'emitcode.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'emitaux.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'emit.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'effect_analysis.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'domainstate.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'dll.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'depend.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'deadcode.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'datarepr.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'dataflow.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'convert_primitives.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'config_main.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'config_boot.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compilenv.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmx_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compile.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'compenv.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'comballoc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'coloring.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmxs_format.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmt2annot.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmmgen_state.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmmgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmm_invariants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'cmm_helpers.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_offsets.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_middle_end.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_conversion_aux.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure_conversion.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'closure.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ccomp.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytepackager.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytelink.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytelibrarian.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bytegen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'builtin_attributes.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'build_export_info.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'branch_relaxation_intf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'branch_relaxation.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'binutils.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'augment_specialised_args.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'attr_helper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ast_mapper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ast_iterator.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ast_invariants.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'ast_helper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asmpackager.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asmlink.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asmlibrarian.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'asmgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'arg_helper.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'alias_analysis.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'afl_instrument.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'CSEgen.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'CSE.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalMod.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'camlinternalFormat.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'yojson_biniou.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_io.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_inbuf.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_vint.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_util.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_stream.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'bi_dump.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-deps.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc-parser.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-astring.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-cmdliner.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-fpath.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-result.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-tyxml.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-fmt.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-stdlib.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-yojson.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-biniou.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_xref_test.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_xref2.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_odoc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_html_support_files.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_model_desc.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_model.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_manpage.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_loader.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_latex.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_html.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_document.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_examples.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-interface.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-contributing.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-driver.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-parent_child_spec.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-features.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-interface.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-odoc_for_authors.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-dune.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'link' 'page-ocamldoc_differences.odoc' '-I' '.' +$ '../src/odoc/bin/main.exe' 'html-generate' 'src-source.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_xref_test__Common.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compmisc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'clflags.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/cmt.pp.ml' 'odoc_loader__Cmt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/cmti.pp.ml' 'odoc_loader__Cmti.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/ident_env.pp.ml' 'odoc_loader__Ident_env.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/compat.ml' 'odoc_model__Compat.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/resolver.ml' 'odoc_odoc__Resolver.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/fs.ml' 'odoc_odoc__Fs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/or_error.ml' 'odoc_odoc__Or_error.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_odoc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/odoc_loader.pp.ml' 'odoc_loader.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/source_info.pp.ml' 'odoc_loader__Source_info.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/lookup_def.pp.ml' 'odoc_loader__Lookup_def.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_loader__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'fpath.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmt_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/compile.ml' 'odoc_xref2__Compile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/tools.ml' 'odoc_xref2__Tools.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/find.ml' 'odoc_xref2__Find.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/errors.ml' 'odoc_xref2__Errors.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/lookup_failures.ml' 'odoc_xref2__Lookup_failures.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/env.ml' 'odoc_xref2__Env.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/component.ml' 'odoc_xref2__Component.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/cfrag.ml' 'odoc_xref2__Cfrag.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/cpath.ml' 'odoc_xref2__Cpath.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/ident.ml' 'odoc_xref2__Ident.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_xref2.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/lang.ml' 'odoc_model__Lang.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/root.ml' 'odoc_model__Root.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/error.ml' 'odoc_model__Error.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/comment.ml' 'odoc_model__Comment.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/location_.ml' 'odoc_model__Location_.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/paths.ml' 'odoc_model__Paths.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/paths_types.ml' 'odoc_model__Paths_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/names.ml' 'odoc_model__Names.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Ast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Warning.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Loc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/odoc_model.ml' 'odoc_model.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_model__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'astring.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_xref_test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parse.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'profile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'result.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Arg.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Array.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__List.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Printf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Result.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'toploop.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Obj.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Int32.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typemod.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_variance.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_separability.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_immediacy.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_properties.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'includemod.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'includecore.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedtree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'diffing_with_keys.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'diffing.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ctype.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'errortrace.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'env.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'subst.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'load_path.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmi_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'misc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__String.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Digest.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'build_path_prefix_map.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'btype.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'shape.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'primitive.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'path.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'outcometree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'type_immediacy.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parsetree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'longident.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ident.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'identifiable.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Set.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Map.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Hashtbl.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asttypes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'location.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Domain.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Buffer.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Uchar.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Seq.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Either.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'warnings.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Sys.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Lexing.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Lazy.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalLazy.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalFormatBasics.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/utils.ml' 'odoc_xref2__Utils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/type_of.ml' 'odoc_xref2__Type_of.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/subst.ml' 'odoc_xref2__Subst.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/strengthen.ml' 'odoc_xref2__Strengthen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/ref_tools.ml' 'odoc_xref2__Ref_tools.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/link.ml' 'odoc_xref2__Link.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/lang_of.ml' 'odoc_xref2__Lang_of.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/xref2/expand_tools.ml' 'odoc_xref2__Expand_tools.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/url.ml' 'odoc_odoc__Url.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/link.ml' 'odoc_html__Link.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/latex/generator.ml' 'odoc_latex__Generator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_latex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/semantics.ml' 'odoc_model__Semantics.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/html_page.ml' 'odoc_odoc__Html_page.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/config.ml' 'odoc_html__Config.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/types.ml' 'odoc_html__Types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/odoc_html.ml' 'odoc_html.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_html__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/renderer.ml' 'odoc_document__Renderer.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/reason.ml' 'odoc_document__Reason.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/ML.ml' 'odoc_document__ML.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/types.ml' 'odoc_document__Types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/url.ml' 'odoc_document__Url.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_document.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tyxml.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tyxml_html.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'html_sigs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'html_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tyxml_svg.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'svg_sigs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'svg_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tyxml_xml.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_stream.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_sigs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_wrap.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/support_files.ml' 'odoc_odoc__Support_files.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/source_tree.ml' 'odoc_odoc__Source_tree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/rendering.ml' 'odoc_odoc__Rendering.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/odoc_link.ml' 'odoc_odoc__Odoc_link.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/odoc_file.ml' 'odoc_odoc__Odoc_file.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/man_page.ml' 'odoc_odoc__Man_page.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/manpage/generator.ml' 'odoc_manpage__Generator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_manpage.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/latex.ml' 'odoc_odoc__Latex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/html_fragment.ml' 'odoc_odoc__Html_fragment.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/depends.ml' 'odoc_odoc__Depends.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/odoc/compile.ml' 'odoc_odoc__Compile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html_support_files/odoc_html_support_files.ml' 'odoc_html_support_files.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model_desc/type_desc.ml' 'odoc_model_desc__Type_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_model_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model_desc/paths_desc.ml' 'odoc_model_desc__Paths_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model_desc/lang_desc.ml' 'odoc_model_desc__Lang_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model_desc/comment_desc.ml' 'odoc_model_desc__Comment_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_model_semantics_test__Test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_model_semantics_test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__BytesLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Int64.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__ListLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__MoreLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Nativeint.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Printexc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__StdLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__StringLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'yojson.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_outbuf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_share.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/reference.ml' 'odoc_model__Reference.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/model/predefined.ml' 'odoc_model__Predefined.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/manpage/link.ml' 'odoc_manpage__Link.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/uid.pp.ml' 'odoc_loader__Uid.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/local_jmp.pp.ml' 'odoc_loader__Local_jmp.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/doc_attr.pp.ml' 'odoc_loader__Doc_attr.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/loader/cmi.pp.ml' 'odoc_loader__Cmi.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/latex/types.ml' 'odoc_latex__Types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/latex/raw.ml' 'odoc_latex__Raw.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'fmt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Stack.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Queue.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/utils.ml' 'odoc_html__Utils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Char.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/html_source.ml' 'odoc_html__Html_source.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/html_page.ml' 'odoc_html__Html_page.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/html_fragment_json.ml' 'odoc_html__Html_fragment_json.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/html/generator.ml' 'odoc_html__Generator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/utils.ml' 'odoc_document__Utils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/targets.ml' 'odoc_document__Targets.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/generator_signatures.ml' 'odoc_document__Generator_signatures.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/codefmt.ml' 'odoc_document__Codefmt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/generator.ml' 'odoc_document__Generator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/doctree.ml' 'odoc_document__Doctree.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/compat.ml' 'odoc_document__Compat.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' '--source' '../src/document/comment.ml' 'odoc_document__Comment.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Wrapping.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Unexposed.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Resolution.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Markup.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples__Expansion.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_examples.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Token.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Syntax.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Parse_error.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'odoc_parser__Lexer.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmdliner.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_print.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'xml_iter.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'svg_f.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'html_f.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'fmt_tty.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'fmt_cli.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unixLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unix.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Bigarray.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Complex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'thread.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'event.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'str.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Weak.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Unit.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Semaphore.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Scanf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Random.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Parsing.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Out_channel.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Option.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Oo.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalOO.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Mutex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Marshal.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Int.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__In_channel.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Gc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Fun.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Float.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Filename.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Ephemeron.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Effect.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Condition.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Callback.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Bytes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Bool.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__Atomic.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stdlib__ArrayLabels.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'std_exit.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'runtime_events.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'profiling.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ocamlmktop_init.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topcommon.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'genprintval.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'dynlink.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_proc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_ast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_masm.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_gas.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'x86_dsl.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'variable.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'internal_variable_names.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'debuginfo.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compilation_unit.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linkage_name.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'var_within_closure.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_element.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'untypeast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unbox_specialised_args.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inline_and_simplify_aux.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_stats_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_cost.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'backend_intf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simple_value_approx.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'freshening.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tag.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'symbol.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'static_exception.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'set_of_closures_origin.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'set_of_closures_id.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'projection.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parameter.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'numbers.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'mutable_variable.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'export_id.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_origin.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_id.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'clambda_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'allocated_const.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unbox_free_vars_of_closures.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'unbox_closures.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'un_anf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'clambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'backend_var.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typetexp.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typeopt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typedecl_unboxed.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typecore.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'typeclass.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'traverse_for_exported_symbols.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'export_info.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translprim.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translobj.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translmod.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translcore.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translclass.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'translattribute.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'trace.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topstart.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topmain.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tophooks.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topeval.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'topdirs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tmc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'terminfo.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tast_mapper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'tast_iterator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'targetint.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'syntaxerr.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'symtable.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmo_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'switch.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'stypes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'annot.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'strongly_connected_components.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'strmatch.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmm.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'split.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'mach.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'reg.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'arch.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'config.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'spill.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplify_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplify_common.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplify_boxed_integer_ops_intf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplify_boxed_integer_ops.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'simplif.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'signature_group.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'share_constants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'semantics_of_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'selection.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'selectgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'scheduling.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linear.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'schedgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'runtimedef.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'remove_unused_program_constructs.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'remove_unused_closure_vars.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'remove_unused_arguments.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'remove_free_vars_equal_to_args.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'reloadgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'reload.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ref_to_variables.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'rec_check.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'proc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printtyped.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printtyp.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printpat.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printmach.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printlinear.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printlambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printinstr.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'instruct.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printcmm.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printclambda_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printclambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'printast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'predef.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'pprintast.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'pparse.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'polling.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'persistent_env.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lazy_backtrack.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'consistbl.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'patterns.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'pass_wrapper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parser.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'docstrings.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalMenhirLib.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'parmatch.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'optmaindriver.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'optmain.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'opterrors.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'optcompile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compile_common.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'oprint.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'opcodes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'mtype.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'meta.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'matching.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'makedepend.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'maindriver.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'main_args.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'main.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'local_store.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'liveness.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linscan.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linearize.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'linear_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lift_let_to_initialize_symbol.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lift_constants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lift_code.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'lexer.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'invariant_params.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'interval.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'interf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'int_replace_polymorphic_compare.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_transforms.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_decision_intf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_stats.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inlining_decision.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inline_and_simplify.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'initialize_symbol_to_let_symbol.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'inconstant_idents.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'includemod_errorprinter.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'includeclass.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'import_approx.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'id_types.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_utils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_to_clambda.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_middle_end.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_iterators.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'flambda_invariants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'find_recursive_functions.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'extract_projections.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'expunge.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytesections.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'export_info_for_pack.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'errors.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'envaux.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'emitenv.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'emitcode.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'emitaux.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'emit.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'effect_analysis.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'domainstate.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'dll.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'depend.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'deadcode.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'datarepr.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'dataflow.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'convert_primitives.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'config_main.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'config_boot.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compilenv.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmx_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compile.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'compenv.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'comballoc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'coloring.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmxs_format.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmt2annot.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmmgen_state.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmmgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmm_invariants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'cmm_helpers.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_offsets.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_middle_end.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_conversion_aux.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure_conversion.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'closure.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ccomp.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytepackager.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytelink.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytelibrarian.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bytegen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'builtin_attributes.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'build_export_info.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'branch_relaxation_intf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'branch_relaxation.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'binutils.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'augment_specialised_args.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'attr_helper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ast_mapper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ast_iterator.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ast_invariants.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'ast_helper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asmpackager.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asmlink.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asmlibrarian.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'asmgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'arg_helper.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'alias_analysis.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'afl_instrument.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'CSEgen.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'CSE.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalMod.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'camlinternalFormat.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'yojson_biniou.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_io.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_inbuf.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_vint.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_util.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_stream.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'bi_dump.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-deps.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc-parser.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-astring.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-cmdliner.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-fpath.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-result.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-tyxml.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-fmt.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-stdlib.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-yojson.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-biniou.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_xref_test.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_xref2.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_odoc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_html_support_files.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_model_desc.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_model.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_manpage.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_loader.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_latex.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_html.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_document.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_examples.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-interface.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-contributing.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-driver.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-parent_child_spec.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-features.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-interface.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-odoc_for_authors.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-dune.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'html-generate' 'page-ocamldoc_differences.odocl' '-o' 'html' '--theme-uri' 'odoc' '--support-uri' 'odoc' +$ '../src/odoc/bin/main.exe' 'support-files' '-o' 'html/odoc' +- : unit = () ]} diff --git a/doc/library_mlds/odoc_html_support_files.mld b/doc/library_mlds/odoc_html_support_files.mld new file mode 100644 index 0000000000..f3ceb0b1d8 --- /dev/null +++ b/doc/library_mlds/odoc_html_support_files.mld @@ -0,0 +1,3 @@ +{0 odoc_html_support_files} + +{!childmodule-Odoc_html_support_files} diff --git a/doc/library_mlds/stdlib.mld b/doc/library_mlds/stdlib.mld index 555fad8554..d1fc783bb9 100644 --- a/doc/library_mlds/stdlib.mld +++ b/doc/library_mlds/stdlib.mld @@ -6,7 +6,6 @@ {!module-Annot} {!module-Arch} {!module-Arg_helper} -{!module-Arith_status} {!module-Asmgen} {!module-Asmlibrarian} {!module-Asmlink} @@ -18,10 +17,8 @@ {!module-Asttypes} {!module-Attr_helper} {!module-Augment_specialised_args} -{!module-Available_regs} {!module-Backend_intf} {!module-Backend_var} -{!module-Big_int} {!module-Bigarray} {!module-Branch_relaxation} {!module-Branch_relaxation_intf} @@ -72,8 +69,6 @@ {!module-Compile_common} {!module-Compilenv} {!module-Compmisc} -{!module-Compute_ranges} -{!module-Compute_ranges_intf} {!module-Condition} {!module-Config} {!module-Consistbl} @@ -155,8 +150,6 @@ {!module-Mtype} {!module-Mutable_variable} {!module-Mutex} -{!module-Nat} -{!module-Num} {!module-Numbers} {!module-Opcodes} {!module-Oprint} @@ -191,12 +184,9 @@ {!module-Profile} {!module-Profiling} {!module-Projection} -{!module-Ratio} {!module-Rec_check} {!module-Ref_to_variables} {!module-Reg} -{!module-Reg_availability_set} -{!module-Reg_with_debug_info} {!module-Reload} {!module-Reloadgen} {!module-Remove_free_vars_equal_to_args} @@ -238,7 +228,6 @@ {!module-Tast_mapper} {!module-Terminfo} {!module-Thread} -{!module-ThreadUnix} {!module-Topdirs} {!module-Toploop} {!module-Topmain} diff --git a/doc/library_mlds/yojson.mld b/doc/library_mlds/yojson.mld index 57e14ec7ac..25a8443794 100644 --- a/doc/library_mlds/yojson.mld +++ b/doc/library_mlds/yojson.mld @@ -1,5 +1,4 @@ {0 Yojson} {!module-Yojson} -{!module-Yojson_biniou} diff --git a/src/compat/compatcmdliner.ml b/src/compat/compatcmdliner.ml index aec41df180..191458c96e 100644 --- a/src/compat/compatcmdliner.ml +++ b/src/compat/compatcmdliner.ml @@ -61,6 +61,10 @@ module Arg = struct let bool = bool let ( & ) = ( & ) + + let conv = conv + let conv_parser = conv_parser + let conv_printer = conv_printer end [@@@ocaml.warning "+3"] diff --git a/src/document/ML.mli b/src/document/ML.mli index a0f8b0f051..94523fc400 100644 --- a/src/document/ML.mli +++ b/src/document/ML.mli @@ -14,7 +14,18 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) -val compilation_unit : Odoc_model.Lang.Compilation_unit.t -> Types.Page.t +open Odoc_model +open Odoc_model.Paths -val page : Odoc_model.Lang.Page.t -> Types.Page.t +val compilation_unit : Lang.Compilation_unit.t -> Types.Document.t + +val page : Lang.Page.t -> Types.Document.t (** Convert compilation unit or page models into a document *) + +val source_tree : Lang.SourceTree.t -> Types.Document.t list + +val source_page : + Identifier.SourcePage.t -> + Lang.Source_info.infos -> + string -> + Types.Document.t diff --git a/src/document/comment.ml b/src/document/comment.ml index e02fcc1baf..0e466f05ba 100644 --- a/src/document/comment.ml +++ b/src/document/comment.ml @@ -309,7 +309,8 @@ let heading let title = non_link_inline_element_list text in let level = heading_level_to_int attrs.Comment.heading_level in let label = Some label in - Item.Heading { label; level; title } + let source_anchor = None in + Item.Heading { label; level; title; source_anchor } let item_element : Comment.block_element -> Item.t list = function | #Comment.attached_block_element as e -> diff --git a/src/document/doctree.ml b/src/document/doctree.ml index 33461ea42a..fdc73b3839 100644 --- a/src/document/doctree.ml +++ b/src/document/doctree.ml @@ -62,7 +62,7 @@ end = struct | Include { content = { status; content; _ }; _ } -> if on_sub status then Rec content else Skip | Heading { label = None; _ } -> Skip - | Heading { label = Some label; level; title } -> + | Heading { label = Some label; level; title; _ } -> Heading ((label, title), level) let node mkurl (anchor, text) children = @@ -150,9 +150,9 @@ module Shift = struct and walk_item ~on_sub shift_state (l : Item.t list) = match l with | [] -> [] - | Heading { label; level; title } :: rest -> + | Heading { label; level; title; source_anchor } :: rest -> let shift_state, level = shift shift_state level in - Item.Heading { label; level; title } + Item.Heading { label; level; title; source_anchor } :: walk_item ~on_sub shift_state rest | Include subp :: rest -> let content = include_ ~on_sub shift_state subp.content in @@ -291,12 +291,13 @@ end = struct end module PageTitle : sig - val render_title : Page.t -> Item.t list + val render_title : ?source_anchor:Url.t -> Page.t -> Item.t list + val render_src_title : Source_page.t -> Item.t list end = struct - let format_title kind name = + let format_title ~source_anchor kind name = let mk title = let level = 0 and label = None in - [ Types.Item.Heading { level; label; title } ] + [ Types.Item.Heading { level; label; title; source_anchor } ] in let prefix s = mk (Types.inline (Text (s ^ " ")) :: Codefmt.code (Codefmt.txt name)) @@ -307,6 +308,7 @@ end = struct | `ModuleType -> prefix "Module type" | `ClassType -> prefix "Class type" | `Class -> prefix "Class" + | `SourcePage -> prefix "Source file" | `Page | `LeafPage | `File -> [] let make_name_from_path { Url.Path.name; parent; _ } = @@ -314,8 +316,11 @@ end = struct | None | Some { kind = `Page; _ } -> name | Some p -> Printf.sprintf "%s.%s" p.name name - let render_title (p : Page.t) = - format_title p.url.kind (make_name_from_path p.url) + let render_title ?source_anchor (p : Page.t) = + format_title ~source_anchor p.url.kind (make_name_from_path p.url) + + let render_src_title (p : Source_page.t) = + format_title ~source_anchor:None p.url.kind (make_name_from_path p.url) end module Math : sig diff --git a/src/document/dune b/src/document/dune index e24015e177..da7d8f7f13 100644 --- a/src/document/dune +++ b/src/document/dune @@ -12,4 +12,4 @@ (public_name odoc.document) (instrumentation (backend bisect_ppx)) - (libraries odoc_model fpath)) + (libraries odoc_model fpath astring)) diff --git a/src/document/generator.ml b/src/document/generator.ml index f8b11547f8..a96b478b93 100644 --- a/src/document/generator.ml +++ b/src/document/generator.ml @@ -47,6 +47,15 @@ let path_to_id path = | Error _ -> None | Ok url -> Some url +let source_anchor locs = + match locs with + | Some { Odoc_model.Lang.Locations.anchor = Some anchor; source_parent } -> + Some (Url.Anchor.source_file_from_identifier source_parent ~anchor) + | Some { Odoc_model.Lang.Locations.anchor = None; source_parent } -> + let path = Url.Path.source_file_from_identifier source_parent in + Some (Url.from_path path) + | _ -> None + let attach_expansion ?(status = `Default) (eq, o, e) page text = match page with | None -> O.documentedSrc text @@ -61,6 +70,10 @@ let attach_expansion ?(status = `Default) (eq, o, e) page text = DocumentedSrc. [ Alternative (Expansion { summary; url; status; expansion }) ] +let mk_heading ?(level = 1) ?label text = + let title = [ inline @@ Text text ] in + Item.Heading { label; level; title; source_anchor = None } + (** Returns the preamble as an item. Stop the preamble at the first heading. The rest is inserted into [items]. *) let prepare_preamble comment items = @@ -72,10 +85,10 @@ let prepare_preamble comment items = in (Comment.standalone preamble, Comment.standalone first_comment @ items) -let make_expansion_page url comments items = +let make_expansion_page ~source_anchor url comments items = let comment = List.concat comments in let preamble, items = prepare_preamble comment items in - { Page.preamble; items; url } + { Page.preamble; items; url; source_anchor } include Generator_signatures @@ -183,6 +196,69 @@ module Make (Syntax : SYNTAX) = struct unresolved [ inline @@ Text txt ] end + module Impl = struct + let impl ~infos src = + let l = + infos + |> List.sort (fun (_, (l1, e1)) (_, (l2, e2)) -> + if l1 = l2 then compare e2 e1 + (* If two intervals open at the same time, we open + first the one that closes last *) + else compare l1 l2) + in + let get_src a b = + let in_bound x = min (max x 0) (String.length src) in + let a = in_bound a and b = in_bound b in + let a, b = (min a b, max a b) in + String.sub src a (b - a) + in + let plain_code = function + | "" -> [] + | s -> [ Types.Source_page.Plain_code s ] + in + let min (a : int) b = if a < b then a else b in + let rec extract from to_ list aux = + match list with + | (k, (loc_start, loc_end)) :: q when loc_start < to_ -> + let loc_end = min loc_end to_ in + (* In case of inconsistent [a [b a] b] + we do [a [b b]a] *) + let initial = plain_code (get_src from loc_start) in + let next, q = extract loc_start loc_end q [] in + extract loc_end to_ q + ([ Types.Source_page.Tagged_code (k, List.rev next) ] + @ initial @ aux) + | q -> (plain_code (get_src from to_) @ aux, q) + in + let doc, _ = extract 0 (String.length src) l [] in + List.rev doc + end + + module Source_page : sig + val url : Paths.Identifier.SourcePage.t -> Url.t + val source : + Paths.Identifier.SourcePage.t -> + Lang.Source_info.infos -> + string -> + Source_page.t + end = struct + let path id = Url.Path.source_file_from_identifier id + let url id = Url.from_path (path id) + + let info_of_info url = function + | Lang.Source_info.Syntax s -> Source_page.Syntax s + | Local_jmp (Occurence { anchor }) -> + Link (Url.Anchor.source_anchor url anchor) + | Local_jmp (Def string) -> Anchor string + + let source id infos source_code = + let url = path id in + let mapper (info, loc) = (info_of_info url info, loc) in + let infos = List.map mapper infos in + let contents = Impl.impl ~infos source_code in + { Source_page.url; contents } + end + module Type_expression : sig val type_expr : ?needs_parentheses:bool -> Lang.TypeExpr.t -> text @@ -561,7 +637,14 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "type"; "extension" ] in let anchor = Some (Url.Anchor.extension_decl t) in let doc = Comment.to_ir t.doc in - Item.Declaration { attr; anchor; doc; content } + let source_anchor = + (* Take the anchor from the first constructor only for consistency with + regular variants. *) + match t.constructors with + | hd :: _ -> source_anchor hd.locs + | [] -> None + in + Item.Declaration { attr; anchor; doc; content; source_anchor } let exn (t : Odoc_model.Lang.Exception.t) = let cstr = constructor (t.id :> Paths.Identifier.t) t.args t.res in @@ -574,7 +657,8 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "exception" ] in let anchor = path_to_id t.id in let doc = Comment.to_ir t.doc in - Item.Declaration { attr; anchor; doc; content } + let source_anchor = source_anchor t.locs in + Item.Declaration { attr; anchor; doc; content; source_anchor } let polymorphic_variant ~type_ident (t : Odoc_model.Lang.TypeExpr.Polymorphic_variant.t) = @@ -784,7 +868,8 @@ module Make (Syntax : SYNTAX) = struct let attr = "type" :: (if is_substitution then [ "subst" ] else []) in let anchor = path_to_id t.id in let doc = Comment.to_ir t.doc in - Item.Declaration { attr; anchor; doc; content } + let source_anchor = source_anchor t.locs in + Item.Declaration { attr; anchor; doc; content; source_anchor } end open Type_declaration @@ -798,6 +883,7 @@ module Make (Syntax : SYNTAX) = struct | Abstract -> ([], Syntax.Value.semicolon) | External _ -> ([ "external" ], Syntax.Type.External.semicolon) in + (* TODO: link to source *) let name = Paths.Identifier.name t.id in let content = O.documentedSrc @@ -811,7 +897,8 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "value" ] @ extra_attr in let anchor = path_to_id t.id in let doc = Comment.to_ir t.doc in - Item.Declaration { attr; anchor; doc; content } + let source_anchor = source_anchor t.locs in + Item.Declaration { attr; anchor; doc; content; source_anchor } end open Value @@ -911,7 +998,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "method" ] in let anchor = path_to_id t.id in let doc = Comment.to_ir t.doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor = None } let instance_variable (t : Odoc_model.Lang.InstanceVariable.t) = let name = Paths.Identifier.name t.id in @@ -930,7 +1017,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "value"; "instance-variable" ] in let anchor = path_to_id t.id in let doc = Comment.to_ir t.doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor = None } let inherit_ (ih : Lang.ClassSignature.Inherit.t) = let cte = @@ -944,7 +1031,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "inherit" ] in let anchor = None in let doc = Comment.to_ir ih.doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor = None } let constraint_ (cst : Lang.ClassSignature.Constraint.t) = let content = @@ -953,7 +1040,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [] in let anchor = None in let doc = Comment.to_ir cst.doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor = None } let class_signature (c : Lang.ClassSignature.t) = let rec loop l acc_items = @@ -1007,13 +1094,17 @@ module Make (Syntax : SYNTAX) = struct if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop in + let source_anchor = source_anchor t.locs in let cname, expansion, expansion_doc = match t.expansion with | None -> (O.documentedSrc @@ O.txt name, None, None) | Some csig -> let expansion_doc, items = class_signature csig in let url = Url.Path.from_identifier t.id in - let page = make_expansion_page url [ t.doc; expansion_doc ] items in + let page = + make_expansion_page ~source_anchor url [ t.doc; expansion_doc ] + items + in ( O.documentedSrc @@ path url [ inline @@ Text name ], Some page, Some expansion_doc ) @@ -1033,7 +1124,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "class" ] in let anchor = path_to_id t.id in let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor } let class_type (t : Odoc_model.Lang.ClassType.t) = let name = Paths.Identifier.name t.id in @@ -1041,13 +1132,17 @@ module Make (Syntax : SYNTAX) = struct let virtual_ = if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop in + let source_anchor = source_anchor t.locs in let cname, expansion, expansion_doc = match t.expansion with | None -> (O.documentedSrc @@ O.txt name, None, None) | Some csig -> let url = Url.Path.from_identifier t.id in let expansion_doc, items = class_signature csig in - let page = make_expansion_page url [ t.doc; expansion_doc ] items in + let page = + make_expansion_page ~source_anchor url [ t.doc; expansion_doc ] + items + in ( O.documentedSrc @@ path url [ inline @@ Text name ], Some page, Some expansion_doc ) @@ -1063,7 +1158,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "class-type" ] in let anchor = path_to_id t.id in let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor } end open Class @@ -1171,7 +1266,10 @@ module Make (Syntax : SYNTAX) = struct let url = Url.Path.from_identifier arg.id in let modname = path url [ inline @@ Text name ] in let type_with_expansion = - let content = make_expansion_page url [ expansion_doc ] items in + let content = + make_expansion_page ~source_anchor:None url [ expansion_doc ] + items + in let summary = O.render modtyp in let status = `Default in let expansion = @@ -1202,17 +1300,18 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "module-substitution" ] in let anchor = path_to_id t.id in let doc = Comment.to_ir t.doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor = None } and module_type_substitution (t : Odoc_model.Lang.ModuleTypeSubstitution.t) = let prefix = O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " " in + let source_anchor = None in let modname = Paths.Identifier.name t.id in let modname, expansion_doc, mty = - module_type_manifest ~subst:true modname t.id t.doc (Some t.manifest) - prefix + module_type_manifest ~subst:true ~source_anchor modname t.id t.doc + (Some t.manifest) prefix in let content = O.documentedSrc (prefix ++ modname) @@ -1223,7 +1322,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "module-type" ] in let anchor = path_to_id t.id in let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor } and simple_expansion : Odoc_model.Lang.ModuleType.simple_expansion -> @@ -1254,25 +1353,13 @@ module Make (Syntax : SYNTAX) = struct @@ Url.Anchor.from_identifier (arg.id :> Paths.Identifier.t) in let doc = [] in - [ Item.Declaration { content; anchor; attr; doc } ]) - in - let prelude = - Item.Heading - { - label = Some "parameters"; - level = 1; - title = [ inline @@ Text "Parameters" ]; - } - :: params - and content = - Item.Heading - { - label = Some "signature"; - level = 1; - title = [ inline @@ Text "Signature" ]; - } - :: content + [ + Item.Declaration + { content; anchor; attr; doc; source_anchor = None }; + ]) in + let prelude = mk_heading ~label:"parameters" "Parameters" :: params + and content = mk_heading ~label:"signature" "Signature" :: content in (sg_doc, prelude @ content) and expansion_of_module_type_expr : @@ -1308,6 +1395,7 @@ module Make (Syntax : SYNTAX) = struct | Alias (_, None) -> None | ModuleType e -> expansion_of_module_type_expr e in + let source_anchor = source_anchor t.locs in let modname, status, expansion, expansion_doc = match expansion with | None -> (O.txt modname, `Default, None, None) @@ -1319,9 +1407,13 @@ module Make (Syntax : SYNTAX) = struct in let url = Url.Path.from_identifier t.id in let link = path url [ inline @@ Text modname ] in - let page = make_expansion_page url [ t.doc; expansion_doc ] items in + let page = + make_expansion_page ~source_anchor url [ t.doc; expansion_doc ] + items + in (link, status, Some page, Some expansion_doc) in + (* TODO: link to source *) let intro = O.keyword "module" ++ O.txt " " ++ modname in let summary = O.ignore intro ++ mdexpr_in_decl t.id t.type_ in let modexpr = @@ -1337,7 +1429,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "module" ] in let anchor = path_to_id t.id in let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor } and simple_expansion_in_decl (base : Paths.Identifier.Module.t) se = let rec ty_of_se : @@ -1363,7 +1455,8 @@ module Make (Syntax : SYNTAX) = struct | Alias (mod_path, _) -> Link.from_path (mod_path :> Paths.Path.t) | ModuleType mt -> mty mt - and module_type_manifest ~subst modname id doc manifest prefix = + and module_type_manifest ~subst ~source_anchor modname id doc manifest + prefix = let expansion = match manifest with | None -> None @@ -1375,7 +1468,10 @@ module Make (Syntax : SYNTAX) = struct | Some (expansion_doc, items) -> let url = Url.Path.from_identifier id in let link = path url [ inline @@ Text modname ] in - let page = make_expansion_page url [ doc; expansion_doc ] items in + let page = + make_expansion_page ~source_anchor url [ doc; expansion_doc ] + items + in (link, Some page, Some expansion_doc) in let summary = @@ -1395,8 +1491,10 @@ module Make (Syntax : SYNTAX) = struct O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " " in let modname = Paths.Identifier.name t.id in + let source_anchor = source_anchor t.locs in let modname, expansion_doc, mty = - module_type_manifest ~subst:false modname t.id t.doc t.expr prefix + module_type_manifest ~subst:false ~source_anchor modname t.id t.doc + t.expr prefix in let content = O.documentedSrc (prefix ++ modname) @@ -1407,7 +1505,7 @@ module Make (Syntax : SYNTAX) = struct let attr = [ "module-type" ] in let anchor = path_to_id t.id in let doc = Comment.synopsis ~decl_doc:t.doc ~expansion_doc in - Item.Declaration { attr; anchor; doc; content } + Item.Declaration { attr; anchor; doc; content; source_anchor } and umty_hidden : Odoc_model.Lang.ModuleType.U.expr -> bool = function | Path p -> Paths.Path.(is_hidden (p :> t)) @@ -1616,21 +1714,22 @@ module Make (Syntax : SYNTAX) = struct The documentation from the expansion is not used. *) Comment.to_ir t.doc in - Item.Include { attr; anchor; doc; content } + Item.Include { attr; anchor; doc; content; source_anchor = None } end open Module module Page : sig - val compilation_unit : Lang.Compilation_unit.t -> Page.t + val compilation_unit : Lang.Compilation_unit.t -> Document.t - val page : Lang.Page.t -> Page.t + val page : Lang.Page.t -> Document.t + + val source_tree : Lang.SourceTree.t -> Document.t list end = struct - let pack : Odoc_model.Lang.Compilation_unit.Packed.t -> Item.t list = + let pack : Lang.Compilation_unit.Packed.t -> Item.t list = fun t -> - let open Odoc_model.Lang in let f x = - let id = x.Compilation_unit.Packed.id in + let id = x.Lang.Compilation_unit.Packed.id in let modname = Paths.Identifier.name id in let md_def = O.keyword "module" ++ O.txt " " ++ O.txt modname ++ O.txt " = " @@ -1643,29 +1742,129 @@ module Make (Syntax : SYNTAX) = struct in let attr = [ "modules" ] in let doc = [] in - let decl = { Item.anchor; content; attr; doc } in + let decl = { Item.anchor; content; attr; doc; source_anchor = None } in Item.Declaration decl in List.map f t - let compilation_unit (t : Odoc_model.Lang.Compilation_unit.t) : Page.t = + let compilation_unit (t : Odoc_model.Lang.Compilation_unit.t) = let url = Url.Path.from_identifier t.id in let unit_doc, items = match t.content with | Module sign -> signature sign | Pack packed -> ([], pack packed) in - make_expansion_page url [ unit_doc ] items + let source_anchor = + match t.source_info with + | Some src -> Some (Source_page.url src.id) + | None -> None + in + let page = make_expansion_page ~source_anchor url [ unit_doc ] items in + Document.Page page - let page (t : Odoc_model.Lang.Page.t) : Page.t = + let page (t : Odoc_model.Lang.Page.t) = (*let name = match t.name.iv with `Page (_, name) | `LeafPage (_, name) -> name in*) (*let title = Odoc_model.Names.PageName.to_string name in*) let url = Url.Path.from_identifier t.name in let preamble, items = Sectioning.docs t.content in - { Page.preamble; items; url } + let source_anchor = None in + Document.Page { Page.preamble; items; url; source_anchor } + + let source_tree t = + let dir_pages = t.Odoc_model.Lang.SourceTree.source_children in + let open Paths.Identifier in + let module Set = Set.Make (SourceDir) in + let module M = Map.Make (SourceDir) in + (* mmap is a from a [SourceDir.t] to its [SourceDir.t] and [SourcePage.t] + children *) + let mmap = + let add parent f mmap = + let old_value = + try M.find parent mmap with Not_found -> (Set.empty, []) + in + M.add parent (f old_value) mmap + and add_file file (set, lp) = (set, file :: lp) + and add_dir dir (set, lp) = (Set.add dir set, lp) in + let rec dir_ancestors_add dir mmap = + match dir.iv with + | `SourceDir (parent, _) -> + let mmap = add parent (add_dir dir) mmap in + dir_ancestors_add parent mmap + | `SourceRoot _ -> mmap + in + let file_ancestors_add ({ iv = `SourcePage (parent, _); _ } as file) + mmap = + let mmap = add parent (add_file file) mmap in + dir_ancestors_add parent mmap + in + List.fold_left + (fun mmap file -> file_ancestors_add file mmap) + M.empty dir_pages + in + let page_of_dir (dir : SourceDir.t) (dir_children, file_children) = + let url = Url.Path.source_dir_from_identifier dir in + let block ?(attr = []) desc = Block.{ attr; desc } in + let inline ?(attr = []) desc = Inline.[ { attr; desc } ] in + let header = + let title = inline (Text (SourceDir.name dir)) in + Item.Heading + Heading.{ label = None; level = 0; title; source_anchor = None } + in + let li ?(attr = []) name url = + let link url desc = + Inline.InternalLink + InternalLink.(Resolved (url, [ Inline.{ attr = []; desc } ])) + in + [ block ~attr @@ Block.Inline (inline @@ link url (Text name)) ] + in + let li_of_child child = + match child with + | { iv = `SourceRoot _; _ } -> + assert false (* No [`SourceRoot] is child of a [`SourceDir] *) + | { iv = `SourceDir (_, name); _ } -> + let url = + child |> Url.Path.source_dir_from_identifier |> Url.from_path + in + (name, url) + in + let li_of_file_child ({ iv = `SourcePage (_, name); _ } as child) = + let url = + child |> Url.Path.source_file_from_identifier |> Url.from_path + in + (name, url) + in + let items = + let text ?(attr = []) desc = Item.Text [ { attr; desc } ] in + let list l = Block.List (Block.Unordered, l) in + let list_of_children = + let dir_list = + Set.fold + (fun child acc -> li_of_child child :: acc) + dir_children [] + and file_list = + List.map (fun child -> li_of_file_child child) file_children + in + let sort ?(attr = []) l = + l + |> List.sort (fun (n1, _) (n2, _) -> String.compare n1 n2) + |> List.map (fun (name, url) -> li ~attr name url) + in + sort ~attr:[ "odoc-directory" ] dir_list + @ sort ~attr:[ "odoc-file" ] file_list + in + header + :: [ text ~attr:[ "odoc-folder-list" ] @@ list list_of_children ] + in + Document.Page + { Types.Page.preamble = []; items; url; source_anchor = None } + in + M.fold (fun dir children acc -> page_of_dir dir children :: acc) mmap [] end include Page + + let source_page id infos source_code = + Document.Source_page (Source_page.source id infos source_code) end diff --git a/src/document/generator_signatures.ml b/src/document/generator_signatures.ml index 32d2ddd811..c35af63814 100644 --- a/src/document/generator_signatures.ml +++ b/src/document/generator_signatures.ml @@ -102,7 +102,15 @@ module type SYNTAX = sig end module type GENERATOR = sig - val compilation_unit : Lang.Compilation_unit.t -> Page.t + val compilation_unit : Lang.Compilation_unit.t -> Document.t - val page : Lang.Page.t -> Page.t + val page : Lang.Page.t -> Document.t + + val source_tree : Lang.SourceTree.t -> Document.t list + + val source_page : + Odoc_model.Paths.Identifier.SourcePage.t -> + Lang.Source_info.infos -> + string -> + Document.t end diff --git a/src/document/reason.mli b/src/document/reason.mli index a0f8b0f051..4fffda700f 100644 --- a/src/document/reason.mli +++ b/src/document/reason.mli @@ -14,7 +14,19 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) -val compilation_unit : Odoc_model.Lang.Compilation_unit.t -> Types.Page.t +open Odoc_model +open Odoc_model.Paths -val page : Odoc_model.Lang.Page.t -> Types.Page.t +val compilation_unit : Lang.Compilation_unit.t -> Types.Document.t + +val page : Lang.Page.t -> Types.Document.t (** Convert compilation unit or page models into a document *) + +val source_tree : Lang.SourceTree.t -> Types.Document.t list + +val source_page : + Identifier.SourcePage.t -> + Lang.Source_info.infos -> + string -> + Types.Document.t +(** Highlight the source as OCaml syntax *) diff --git a/src/document/renderer.ml b/src/document/renderer.ml index a06dc32b90..cee635dab6 100644 --- a/src/document/renderer.ml +++ b/src/document/renderer.ml @@ -17,12 +17,28 @@ let traverse ~f t = in List.iter aux t -type 'a t = { name : string; render : 'a -> Types.Page.t -> page list } +type 'a t = { + name : string; + render : 'a -> Types.Document.t -> page list; + extra_documents : + 'a -> + Odoc_model.Lang.Compilation_unit.t -> + syntax:syntax -> + Types.Document.t list; +} let document_of_page ~syntax v = match syntax with Reason -> Reason.page v | OCaml -> ML.page v +let documents_of_source_tree ~syntax v = + match syntax with Reason -> Reason.source_tree v | OCaml -> ML.source_tree v + let document_of_compilation_unit ~syntax v = match syntax with | Reason -> Reason.compilation_unit v | OCaml -> ML.compilation_unit v + +let document_of_source ~syntax = + match syntax with + | Reason -> Reason.source_page (* Currently, both functions are equivalent *) + | OCaml -> ML.source_page diff --git a/src/document/types.ml b/src/document/types.ml index 969f2c28b8..ee46776be5 100644 --- a/src/document/types.ml +++ b/src/document/types.ml @@ -65,7 +65,13 @@ end = Description and Heading : sig - type t = { label : string option; level : int; title : Inline.t } + type t = { + label : string option; + level : int; + title : Inline.t; + source_anchor : Url.t option; + (** Used for the source link of the item displayed on the page. *) + } end = Heading @@ -142,10 +148,9 @@ and Item : sig anchor : Url.Anchor.t option; content : 'a; doc : Block.t; + source_anchor : Url.Anchor.t option; } - type declaration = DocumentedSrc.t item - type text = Block.t type t = @@ -157,10 +162,31 @@ end = Item and Page : sig - type t = { preamble : Item.t list; items : Item.t list; url : Url.Path.t } + type t = { + preamble : Item.t list; + items : Item.t list; + url : Url.Path.t; + source_anchor : Url.t option; + (** Url to the corresponding source code. Might be a whole source file + or a sub part. *) + } end = Page +and Source_page : sig + type info = Syntax of string | Anchor of string | Link of Url.Anchor.t + + type code = span list + and span = Tagged_code of info * code | Plain_code of string + + type t = { url : Url.Path.t; contents : code } +end = + Source_page + +module Document = struct + type t = Page of Page.t | Source_page of Source_page.t +end + let inline ?(attr = []) desc = Inline.{ attr; desc } let block ?(attr = []) desc = Block.{ attr; desc } diff --git a/src/document/url.ml b/src/document/url.ml index 92d6ba5a86..9aaa0eae23 100644 --- a/src/document/url.ml +++ b/src/document/url.ml @@ -101,7 +101,8 @@ module Path = struct | `Parameter of int | `Class | `ClassType - | `File ] + | `File + | `SourcePage ] let string_of_kind : kind -> string = function | `Page -> "page" @@ -112,6 +113,7 @@ module Path = struct | `Class -> "class" | `ClassType -> "class-type" | `File -> "file" + | `SourcePage -> "source" let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind) @@ -181,6 +183,20 @@ module Path = struct from_identifier (p : [< source_pv ] Odoc_model.Paths.Identifier.id :> source) + let rec source_dir_from_identifier id = + match id.Odoc_model.Paths.Identifier.iv with + | `SourceRoot container -> from_identifier (container :> source) + | `SourceDir (parent, name) -> + let parent = source_dir_from_identifier parent in + let kind = `Page in + mk ~parent kind name + + let source_file_from_identifier id = + let (`SourcePage (parent, name)) = id.Odoc_model.Paths.Identifier.iv in + let parent = source_dir_from_identifier parent in + let kind = `SourcePage in + mk ~parent kind name + let to_list url = let rec loop acc { parent; name; kind } = match parent with @@ -222,7 +238,8 @@ module Anchor = struct | `Method | `Val | `Constructor - | `Field ] + | `Field + | `SourceAnchor ] let string_of_kind : kind -> string = function | #Path.kind as k -> Path.string_of_kind k @@ -235,6 +252,7 @@ module Anchor = struct | `Val -> "val" | `Constructor -> "constructor" | `Field -> "field" + | `SourceAnchor -> "source-anchor" let pp_kind fmt kind = Format.fprintf fmt "%s" (string_of_kind kind) @@ -361,6 +379,11 @@ module Anchor = struct Error (Unexpected_anchor "core_type label parent") | { iv = `Type (gp, _); _ } -> mk ~kind:`Section gp str_name) + let source_file_from_identifier id ~anchor = + let kind = `SourceAnchor in + let page = Path.source_file_from_identifier id in + { page; anchor; kind } + let polymorphic_variant ~type_ident elt = let name_of_type_constr te = match te with @@ -391,6 +414,8 @@ module Anchor = struct let first_cons = Identifier.name (List.hd decl.constructors).id in let anchor = Format.asprintf "%a-%s" pp_kind kind first_cons in { page; kind; anchor } + + let source_anchor path anchor = { page = path; anchor; kind = `SourceAnchor } end type kind = Anchor.kind diff --git a/src/document/url.mli b/src/document/url.mli index 9d448dd176..66a658e082 100644 --- a/src/document/url.mli +++ b/src/document/url.mli @@ -20,7 +20,8 @@ module Path : sig | `Parameter of int | `Class | `ClassType - | `File ] + | `File + | `SourcePage ] val pp_kind : Format.formatter -> kind -> unit @@ -37,6 +38,13 @@ module Path : sig val from_identifier : [< source_pv ] Odoc_model.Paths.Identifier.id -> t + val source_dir_from_identifier : Odoc_model.Paths.Identifier.SourceDir.t -> t + (** A path to a source dir. *) + + val source_file_from_identifier : + Odoc_model.Paths.Identifier.SourcePage.t -> t + (** A path to a source file. *) + val to_list : t -> (kind * string) list val of_list : (kind * string) list -> t option @@ -67,7 +75,8 @@ module Anchor : sig | `Method | `Val | `Constructor - | `Field ] + | `Field + | `SourceAnchor ] val pp_kind : Format.formatter -> kind -> unit @@ -84,6 +93,9 @@ module Anchor : sig val from_identifier : Identifier.t -> (t, Error.t) result + val source_file_from_identifier : + Odoc_model.Paths.Identifier.SourcePage.t -> anchor:string -> t + val polymorphic_variant : type_ident:Identifier.t -> Odoc_model.Lang.TypeExpr.Polymorphic_variant.element -> @@ -92,6 +104,8 @@ module Anchor : sig val extension_decl : Odoc_model.Lang.Extension.t -> t (** Anchor for the extension declaration item itself, which doesn't have an identifier in the model. *) + + val source_anchor : Path.t -> string -> t end type kind = Anchor.kind diff --git a/src/html/generator.ml b/src/html/generator.ml index a18dc216f8..88b2105132 100644 --- a/src/html/generator.ml +++ b/src/html/generator.ml @@ -17,6 +17,7 @@ open Odoc_document.Types module Html = Tyxml.Html module Doctree = Odoc_document.Doctree +module Url = Odoc_document.Url type any = Html_types.flow5 @@ -34,12 +35,23 @@ let mk_anchor_link id = let mk_anchor anchor = match anchor with | None -> ([], [], []) - | Some { Odoc_document.Url.Anchor.anchor; _ } -> + | Some { Url.Anchor.anchor; _ } -> let link = mk_anchor_link anchor in let extra_attr = [ Html.a_id anchor ] in let extra_class = [ "anchored" ] in (extra_attr, extra_class, link) +let mk_link_to_source ~config ~resolve anchor = + match anchor with + | None -> [] + | Some url -> + let href = Link.href ~config ~resolve url in + [ + Html.a + ~a:[ Html.a_href href; Html.a_class [ "source_link" ] ] + [ Html.txt "Source" ]; + ] + let class_ (l : Class.t) = if l = [] then [] else [ Html.a_class l ] let inline_math (s : Math.t) = @@ -155,6 +167,7 @@ let heading ~config ~resolve (h : Heading.t) = | None -> ([], []) in let content = inline ~config ~resolve h.title in + let source_link = mk_link_to_source ~config ~resolve h.source_anchor in let mk = match h.level with | 0 -> Html.h1 @@ -164,7 +177,7 @@ let heading ~config ~resolve (h : Heading.t) = | 4 -> Html.h5 | _ -> Html.h6 in - mk ~a (anchor @ content) + mk ~a (anchor @ content @ source_link) let rec block ~config ~resolve (l : Block.t) : flow Html.elt list = let as_flow x = (x : phrasing Html.elt list :> flow Html.elt list) in @@ -298,7 +311,14 @@ and items ~config ~resolve l : item Html.elt list = (continue_with [@tailcall]) rest content | Heading h :: rest -> (continue_with [@tailcall]) rest [ heading ~config ~resolve h ] - | Include { attr; anchor; doc; content = { summary; status; content } } + | Include + { + attr; + anchor; + source_anchor; + doc; + content = { summary; status; content }; + } :: rest -> let doc = spec_doc_div ~config ~resolve doc in let included_html = (items content :> item Html.elt list) in @@ -311,8 +331,11 @@ and items ~config ~resolve l : item Html.elt list = let open' = if open' then [ Html.a_open () ] else [] in let summary = let extra_attr, extra_class, anchor_link = mk_anchor anchor in + let link_to_source = + mk_link_to_source ~config ~resolve source_anchor + in let a = spec_class (attr @ extra_class) @ extra_attr in - Html.summary ~a @@ anchor_link + Html.summary ~a @@ anchor_link @ link_to_source @ source (inline ~config ~resolve) summary in let inner = @@ -330,10 +353,13 @@ and items ~config ~resolve l : item Html.elt list = | `Default -> details ~open':(Config.open_details config) in (continue_with [@tailcall]) rest content - | Declaration { Item.attr; anchor; content; doc } :: rest -> + | Declaration { Item.attr; anchor; source_anchor; content; doc } :: rest -> let extra_attr, extra_class, anchor_link = mk_anchor anchor in + let link_to_source = mk_link_to_source ~config ~resolve source_anchor in let a = spec_class (attr @ extra_class) @ extra_attr in - let content = anchor_link @ documentedSrc ~config ~resolve content in + let content = + anchor_link @ link_to_source @ documentedSrc ~config ~resolve content + in let spec = let doc = spec_doc_div ~config ~resolve doc in [ div ~a:[ Html.a_class [ "odoc-spec" ] ] (div ~a content :: doc) ] @@ -402,11 +428,10 @@ module Page = struct let rec include_ ~config { Subpage.content; _ } = page ~config content - and subpages ~config subpages = - Utils.list_concat_map ~f:(include_ ~config) subpages + and subpages ~config subpages = List.map (include_ ~config) subpages - and page ~config p : Odoc_document.Renderer.page list = - let ({ Page.preamble; items = i; url } as p) = + and page ~config p : Odoc_document.Renderer.page = + let { Page.preamble; items = i; url; source_anchor } = Doctree.Labels.disambiguate_page ~enter_subpages:false p in let subpages = subpages ~config @@ Doctree.Subpages.compute p in @@ -415,20 +440,41 @@ module Page = struct let uses_katex = Doctree.Math.has_math_elements p in let toc = Toc.gen_toc ~config ~resolve ~path:url i in let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~url in - let header = - items ~config ~resolve (Doctree.PageTitle.render_title p @ preamble) - in let content = (items ~config ~resolve i :> any Html.elt list) in if Config.as_json config then + let source_anchor = + match source_anchor with + | Some url -> Some (Link.href ~config ~resolve url) + | None -> None + in Html_fragment_json.make ~config ~preamble:(items ~config ~resolve preamble :> any Html.elt list) - ~breadcrumbs ~toc ~url ~uses_katex content subpages + ~breadcrumbs ~toc ~url ~uses_katex ~source_anchor content subpages else + let header = + items ~config ~resolve + (Doctree.PageTitle.render_title ?source_anchor p @ preamble) + in Html_page.make ~config ~header ~toc ~breadcrumbs ~url ~uses_katex content subpages + + and source_page ~config sp = + let { Source_page.url; contents } = sp in + let resolve = Link.Current sp.url in + let title = url.Url.Path.name + and doc = Html_source.html_of_doc ~config ~resolve contents in + let breadcrumbs = Breadcrumbs.gen_breadcrumbs ~config ~url in + let header = + items ~config ~resolve (Doctree.PageTitle.render_src_title sp) + in + if Config.as_json config then + Html_fragment_json.make_src ~config ~url ~breadcrumbs [ doc ] + else Html_page.make_src ~breadcrumbs ~header ~config ~url title [ doc ] end -let render ~config page = Page.page ~config page +let render ~config = function + | Document.Page page -> [ Page.page ~config page ] + | Source_page src -> [ Page.source_page ~config src ] let doc ~config ~xref_base_uri b = let resolve = Link.Base xref_base_uri in diff --git a/src/html/generator.mli b/src/html/generator.mli index e1a5139357..265fbd95ab 100644 --- a/src/html/generator.mli +++ b/src/html/generator.mli @@ -1,6 +1,6 @@ val render : config:Config.t -> - Odoc_document.Types.Page.t -> + Odoc_document.Types.Document.t -> Odoc_document.Renderer.page list val doc : diff --git a/src/html/html_fragment_json.ml b/src/html/html_fragment_json.ml index d5b5d8de48..8535662b3b 100644 --- a/src/html/html_fragment_json.ml +++ b/src/html/html_fragment_json.ml @@ -3,6 +3,7 @@ *) module Html = Tyxml.Html +module Url = Odoc_document.Url let json_of_breadcrumbs (breadcrumbs : Types.breadcrumb list) : Utils.Json.json = @@ -11,7 +12,7 @@ let json_of_breadcrumbs (breadcrumbs : Types.breadcrumb list) : Utils.Json.json [ ("name", `String b.name); ("href", `String b.href); - ("kind", `String (Odoc_document.Url.Path.string_of_kind b.kind)); + ("kind", `String (Url.Path.string_of_kind b.kind)); ] in let json_breadcrumbs = breadcrumbs |> List.map breadcrumb in @@ -29,19 +30,25 @@ let json_of_toc (toc : Types.toc list) : Utils.Json.json = let toc_json_list = toc |> List.map section in `Array toc_json_list -let make ~config ~preamble ~url ~breadcrumbs ~toc ~uses_katex content children = +let make ~config ~preamble ~url ~breadcrumbs ~toc ~uses_katex ~source_anchor + content children = let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in let filename = Fpath.add_ext ".json" filename in let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in let json_to_string json = Utils.Json.to_string json in + let source_anchor = + match source_anchor with Some url -> `String url | None -> `Null + in let content ppf = Format.pp_print_string ppf (json_to_string (`Object [ + ("type", `String "documentation"); ("uses_katex", `Bool uses_katex); ("breadcrumbs", json_of_breadcrumbs breadcrumbs); ("toc", json_of_toc toc); + ("source_anchor", source_anchor); ( "preamble", `String (String.concat "" @@ -52,4 +59,24 @@ let make ~config ~preamble ~url ~breadcrumbs ~toc ~uses_katex content children = (List.map (Format.asprintf "%a" htmlpp) content)) ); ])) in - [ { Odoc_document.Renderer.filename; content; children } ] + { Odoc_document.Renderer.filename; content; children } + +let make_src ~config ~url ~breadcrumbs content = + let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in + let filename = Fpath.add_ext ".json" filename in + let htmlpp = Html.pp_elt ~indent:(Config.indent config) () in + let json_to_string json = Utils.Json.to_string json in + let content ppf = + Format.pp_print_string ppf + (json_to_string + (`Object + [ + ("type", `String "source"); + ("breadcrumbs", json_of_breadcrumbs breadcrumbs); + ( "content", + `String + (String.concat "" + (List.map (Format.asprintf "%a" htmlpp) content)) ); + ])) + in + { Odoc_document.Renderer.filename; content; children = [] } diff --git a/src/html/html_fragment_json.mli b/src/html/html_fragment_json.mli index 578dc2cb84..f829dcf1b8 100644 --- a/src/html/html_fragment_json.mli +++ b/src/html/html_fragment_json.mli @@ -7,6 +7,14 @@ val make : breadcrumbs:Types.breadcrumb list -> toc:Types.toc list -> uses_katex:bool -> + source_anchor:string option -> Html_types.div_content Html.elt list -> Odoc_document.Renderer.page list -> - Odoc_document.Renderer.page list + Odoc_document.Renderer.page + +val make_src : + config:Config.t -> + url:Odoc_document.Url.Path.t -> + breadcrumbs:Types.breadcrumb list -> + Html_types.div_content Html.elt list -> + Odoc_document.Renderer.page diff --git a/src/html/html_page.ml b/src/html/html_page.ml index 0fa94b085e..d314013b93 100644 --- a/src/html/html_page.ml +++ b/src/html/html_page.ml @@ -14,6 +14,7 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +module Url = Odoc_document.Url module Html = Tyxml.Html let html_of_toc toc = @@ -83,11 +84,8 @@ let page_creator ~config ~url ~uses_katex header breadcrumbs toc content = match base with | Types.Absolute uri -> uri ^ "/" ^ file | Relative uri -> - let page = - Odoc_document.Url.Path.{ kind = `File; parent = uri; name = file } - in - Link.href ~config ~resolve:(Current url) - (Odoc_document.Url.from_path page) + let page = Url.Path.{ kind = `File; parent = uri; name = file } in + Link.href ~config ~resolve:(Current url) (Url.from_path page) in let odoc_css_uri = file_uri theme_uri "odoc.css" in @@ -156,4 +154,64 @@ let make ~config ~url ~header ~breadcrumbs ~toc ~uses_katex content children = let content = page_creator ~config ~url ~uses_katex header breadcrumbs toc content in - [ { Odoc_document.Renderer.filename; content; children } ] + { Odoc_document.Renderer.filename; content; children } + +let path_of_module_of_source ppf url = + match url.Url.Path.parent with + | Some parent -> + let path = Link.Path.for_printing parent in + Format.fprintf ppf " (%s)" (String.concat "." path) + | None -> () + +let src_page_creator ~breadcrumbs ~config ~url ~header name content = + let theme_uri = Config.theme_uri config in + let head : Html_types.head Html.elt = + let title_string = + Format.asprintf "Source: %s%a" name path_of_module_of_source url + in + let file_uri base file = + match base with + | Types.Absolute uri -> uri ^ "/" ^ file + | Relative uri -> + let page = Url.Path.{ kind = `File; parent = uri; name = file } in + Link.href ~config ~resolve:(Current url) (Url.from_path page) + in + let odoc_css_uri = file_uri theme_uri "odoc.css" in + let meta_elements = + [ + Html.link ~rel:[ `Stylesheet ] ~href:odoc_css_uri (); + Html.meta ~a:[ Html.a_charset "utf-8" ] (); + Html.meta + ~a:[ Html.a_name "generator"; Html.a_content "odoc %%VERSION%%" ] + (); + Html.meta + ~a: + [ + Html.a_name "viewport"; + Html.a_content "width=device-width,initial-scale=1.0"; + ] + (); + ] + in + Html.head (Html.title (Html.txt title_string)) meta_elements + in + let body = + html_of_breadcrumbs breadcrumbs + @ [ Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] header ] + @ content + in + (* We never indent as there is a bug in tyxml and it would break lines inside + a [pre] *) + let htmlpp = Html.pp ~indent:false () in + let html = + Html.html head (Html.body ~a:[ Html.a_class [ "odoc-src" ] ] body) + in + let content ppf = htmlpp ppf html in + content + +let make_src ~config ~url ~breadcrumbs ~header title content = + let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in + let content = + src_page_creator ~breadcrumbs ~config ~url ~header title content + in + { Odoc_document.Renderer.filename; content; children = [] } diff --git a/src/html/html_page.mli b/src/html/html_page.mli index f79495f315..e0d4a4b8d7 100644 --- a/src/html/html_page.mli +++ b/src/html/html_page.mli @@ -29,7 +29,19 @@ val make : uses_katex:bool -> Html_types.div_content Html.elt list -> Odoc_document.Renderer.page list -> - Odoc_document.Renderer.page list + Odoc_document.Renderer.page +(** [make ?theme_uri (body, children)] calls "the page creator" to turn [body] + into an [[ `Html ] elt]. If [theme_uri] is provided, it will be used to + locate the theme files, otherwise the HTML output directory is used. *) + +val make_src : + config:Config.t -> + url:Odoc_document.Url.Path.t -> + breadcrumbs:Types.breadcrumb list -> + header:Html_types.flow5_without_header_footer Html.elt list -> + string -> + Html_types.div_content Html.elt list -> + Odoc_document.Renderer.page (** [make ?theme_uri (body, children)] calls "the page creator" to turn [body] into an [[ `Html ] elt]. If [theme_uri] is provided, it will be used to locate the theme files, otherwise the HTML output directory is used. *) diff --git a/src/html/html_source.ml b/src/html/html_source.ml new file mode 100644 index 0000000000..ab08665780 --- /dev/null +++ b/src/html/html_source.ml @@ -0,0 +1,71 @@ +open Odoc_document.Types +open Tyxml + +let html_of_doc ~config ~resolve docs = + let open Html in + let a : + ( [< Html_types.a_attrib ], + [< Html_types.span_content_fun ], + [> Html_types.span ] ) + star = + Unsafe.node "a" + (* Makes it possible to use inside span. Although this is not standard (see + https://developer.mozilla.org/en-US/docs/Web/Guide/HTML/Content_categories) + it is validated by the {{:https://validator.w3.org/nu/#textarea}W3C}. *) + in + (* [a] tags should not contain in other [a] tags. If this happens, browsers + start to be really weird. If PPX do bad things, such a situation could + happen. We manually avoid this situation. *) + let rec doc_to_html ~is_in_a doc = + match doc with + | Source_page.Plain_code s -> [ txt s ] + | Tagged_code (info, docs) -> ( + let is_in_a = match info with Link _ -> true | _ -> is_in_a in + let children = List.concat @@ List.map (doc_to_html ~is_in_a) docs in + match info with + | Syntax tok -> [ span ~a:[ a_class [ tok ] ] children ] + | Link anchor -> + let href = Link.href ~config ~resolve anchor in + [ a ~a:[ a_href href ] children ] + | Anchor lbl -> [ span ~a:[ a_id lbl ] children ]) + in + span ~a:[] @@ List.concat @@ List.map (doc_to_html ~is_in_a:false) docs + +let count_lines_in_string s = + let n = ref 0 in + String.iter (function '\n' -> incr n | _ -> ()) s; + !n + +(** Traverse the doc to count the number of lines. *) +let rec count_lines_in_span = function + | Source_page.Plain_code s -> count_lines_in_string s + | Tagged_code (_, docs) -> count_lines docs + +and count_lines = function + | [] -> 0 + | hd :: tl -> count_lines_in_span hd + count_lines tl + +let rec line_numbers acc n = + let open Html in + if n < 1 then acc + else + let l = string_of_int n in + let anchor = + a + ~a:[ a_id ("L" ^ l); a_class [ "source_line" ]; a_href ("#L" ^ l) ] + [ txt l ] + in + line_numbers (anchor :: txt "\n" :: acc) (n - 1) + +let html_of_doc ~config ~resolve docs = + let open Html in + pre + ~a:[ a_class [ "source_container" ] ] + [ + code + ~a:[ a_class [ "source_line_column" ] ] + (line_numbers [] (count_lines docs)); + code + ~a:[ a_class [ "source_code" ] ] + [ html_of_doc ~config ~resolve docs ]; + ] diff --git a/src/html/html_source.mli b/src/html/html_source.mli new file mode 100644 index 0000000000..1e09f4bd61 --- /dev/null +++ b/src/html/html_source.mli @@ -0,0 +1,5 @@ +val html_of_doc : + config:Config.t -> + resolve:Link.resolve -> + Odoc_document.Types.Source_page.code -> + [> Html_types.pre ] Tyxml.Html.elt diff --git a/src/html/link.ml b/src/html/link.ml index 60e68400f4..ece4b8c001 100644 --- a/src/html/link.ml +++ b/src/html/link.ml @@ -6,7 +6,7 @@ module Path = struct let segment_to_string (kind, name) = match kind with - | `Module | `Page -> name + | `Module | `Page | `File | `SourcePage -> name | _ -> Format.asprintf "%a-%s" Url.Path.pp_kind kind name let is_leaf_page url = url.Url.Path.kind = `LeafPage @@ -15,7 +15,7 @@ module Path = struct let l = Url.Path.to_list url in let is_dir = if is_flat then function `Page -> `Always | _ -> `Never - else function `LeafPage -> `Never | `File -> `Never | _ -> `Always + else function `LeafPage | `File | `SourcePage -> `Never | _ -> `Always in let dir, file = Url.Path.split ~is_dir l in let dir = List.map segment_to_string dir in @@ -24,6 +24,7 @@ module Path = struct | [] -> "index.html" | [ (`LeafPage, name) ] -> name ^ ".html" | [ (`File, name) ] -> name + | [ (`SourcePage, name) ] -> name ^ ".html" | xs -> assert is_flat; String.concat "-" (List.map segment_to_string xs) ^ ".html" diff --git a/src/html/types.mli b/src/html/types.mli deleted file mode 100644 index 04fd5623ad..0000000000 --- a/src/html/types.mli +++ /dev/null @@ -1,18 +0,0 @@ -type uri = - | Absolute of string - | Relative of Odoc_document.Url.Path.t option - (** The type for absolute and relative URIs. The relative URIs are resolved - using the HTML output directory as a target. *) - -type toc = { - title : Html_types.flow5_without_interactive Tyxml.Html.elt list; - title_str : string; - href : string; - children : toc list; -} - -type breadcrumb = { - href : string; - name : string; - kind : Odoc_document.Url.Path.kind; -} diff --git a/src/html_support_files/odoc.css b/src/html_support_files/odoc.css index cc9d74f4ab..b7fc972408 100644 --- a/src/html_support_files/odoc.css +++ b/src/html_support_files/odoc.css @@ -14,6 +14,7 @@ --color: #333333; --link-color: #2C94BD; + --source-color: grey; --anchor-hover: #555; --anchor-color: #d5d5d5; --xref-shadow: #cc6666; @@ -142,6 +143,7 @@ table { html { font-size: 15px; + scroll-behavior: smooth; } body { @@ -149,16 +151,23 @@ body { background: #FFFFFF; color: var(--color); background-color: var(--main-background); + font-family: "Noticia Text", Georgia, serif; + line-height: 1.5; } body { - max-width: 100ex; margin-left: calc(10vw + 20ex); margin-right: 4ex; margin-top: 20px; margin-bottom: 50px; - font-family: "Noticia Text", Georgia, serif; - line-height: 1.5; +} + +body.odoc { + max-width: 100ex; +} + +body.odoc-src { + margin-right: calc(10vw + 20ex); } header { @@ -238,6 +247,10 @@ a { color: var(--link-color); } +.odoc-src pre a { + color: inherit; +} + a:hover { box-shadow: 0 1px 0 0 var(--link-color); } @@ -289,6 +302,14 @@ a.anchor { box-shadow: 0 1px 0 0 var(--xref-shadow); } +/* Source links float inside preformated text or headings. */ +a.source_link { + float: right; + color: var(--source-color); + font-family: "Fira Sans", Helvetica, Arial, sans-serif; + font-size: initial; +} + /* Section and document divisions. Until at least 4.03 many of the modules of the stdlib start at .h7, we restart the sequence there like h2 */ @@ -372,15 +393,15 @@ tt, code, pre { font-weight: 400; } -pre { +.odoc pre { padding: 0.1em; border: 1px solid var(--pre-border-color); border-radius: 5px; overflow-x: auto; } -p code, -li code { +.odoc p code, +.odoc li code { background-color: var(--li-code-background); color: var(--li-code-color); border-radius: 3px; @@ -391,13 +412,13 @@ p a > code { color: var(--link-color); } -code { +.odoc code { white-space: pre-wrap; } /* Code blocks (e.g. Examples) */ -pre code { +.odoc pre code { font-size: 0.893rem; } @@ -676,8 +697,8 @@ td.def-doc *:first-child { /* Mobile adjustements. */ -@media only screen and (max-width: 95ex) { - body.odoc { +@media only screen and (max-width: 110ex) { + body { margin: 2em; } .odoc-toc { @@ -704,6 +725,47 @@ td.def-doc *:first-child { } } +/* Source code. */ + +.source_container { + display: flex; +} + +.source_line_column { + padding-right: 0.5em; + text-align: right; + background: #eee8d5; +} + +.source_line { + padding: 0 1em; +} + +.source_code { + flex-grow: 1; + background: #fdf6e3; + padding: 0 0.3em; + color: #657b83; +} + +/* Source directories */ + +.odoc-directory::before { + content: "📁"; + margin: 0.3em; + font-size: 1.3em; +} + +.odoc-file::before { + content: "📄"; + margin: 0.3em; + font-size: 1.3em; +} + +.odoc-folder-list { + list-style: none; +} + /* Syntax highlighting (based on github-gist) */ .hljs { @@ -777,6 +839,34 @@ td.def-doc *:first-child { text-decoration: underline; } +.VAL, .TYPE, .LET, .REC, .IN, .OPEN, .NONREC, .MODULE, .METHOD, .LETOP, .INHERIT, .INCLUDE, .FUNCTOR, .EXTERNAL, .CONSTRAINT, .ASSERT, .AND, .END, .CLASS, .STRUCT, .SIG { + color: #859900;; +} + +.WITH, .WHILE, .WHEN, .VIRTUAL, .TRY, .TO, .THEN, .PRIVATE, .OF, .NEW, .MUTABLE, .MATCH, .LAZY, .IF, .FUNCTION, .FUN, .FOR, .EXCEPTION, .ELSE, .TO, .DOWNTO, .DO, .DONE, .BEGIN, .AS { + color: #cb4b16; +} + +.TRUE, .FALSE { + color: #b58900; +} + +.failwith, .INT, .SEMISEMI, .LIDENT { + color: #2aa198; +} + +.STRING, .CHAR, .UIDENT { + color: #b58900; +} + +.DOCSTRING { + color: #268bd2; +} + +.COMMENT { + color: #93a1a1; +} + /*--------------------------------------------------------------------------- Copyright (c) 2016 The odoc contributors diff --git a/src/html_support_files/odoc_html_support_files.ml b/src/html_support_files/odoc_html_support_files.ml index c8e1a20255..d04db20b58 100644 --- a/src/html_support_files/odoc_html_support_files.ml +++ b/src/html_support_files/odoc_html_support_files.ml @@ -24,6 +24,8 @@ module Internal = struct let d_0f6a949341647131a618c717cc034d0f = "\022\187\179\226\244jF\194\229\182[t5\215\148e\194\139\007D\153>\225*8$\004\"\025@d\144\136\011\130\138\194|>\014\029R\209\"\202\"J\137\152x\162\225\007)v\006\184\028\181(\200M\141\135|\022\0289\156\151\158\146\164\208=t(\171\242\197\018P\146\178\148\177\248\212\001\169\168NK*\197Z\132\152NI\148I.y\251V\164^\242OSQ\023\143\184'\246d\006xby\210\211&=\174\223zl\1789\215\"\166\144@\017\162\228\t\014D\rI\028\2342\200\170\168g\188\219:\148\158J\001.\2005R\240R\245#\139\220\021\029\n\133\136\018H\018U\138\188\198\128k\165%,\131tQ\n\022!\174,\222:\228\030\232QMAZ\"\tB\129\239\181\177z\201tb\172\022GI\228\031\169\187\004|)\216N\204\194\017\011\187\171\179\154x\174\232\175\022\154'J\174c\005\210A\148B\204\229\140d\131\128\155J\148s\149\196\"\236\155\131[\190\221\012\241\199$\150/\174\180\213\015\170h\225QL\144#\161}\160\160\248\146\230|R\146\128g J\2255\179\002\139\144@\132\017\242\241\226\002\184\006\169\012P\148\212\169TKF\r\206\201\134V\206r\020%\162\147\129\186U\211!-Q\140\020\249b\231\185h\161D\171\206\255\166\160\021\021_&\162#\195P\229Kd\t@\192\213\007\157Y\222\185?i\238\255\1784\247\015\000`\238\190\229(\247\204\127tU\157\145?\000\192\192\128ZL\140\245\0225\148\216B?&\196'O[\136\251\236\172\020:|x\248?\184h6\147lFj{\237Q\203\203\2265Y\142\201\022\167C\170\004\026\169\018%H\148\228\152\189\178XdqH\160F\136\129#1,p\133\178\200(\136P2\1452\225R)\251#$\0175\138\213M\217b\133e\025g\133p\139be\164\129(d%\150\210\255\128H\1330\144+\164\128\144\195i(\025\216\221eSk\018\000&9\228y\213O\029\214\174\200q3\148\203rH-\027\005\163LZz\184\024\022\177\204t\198\237uM\002\b\000\139\204\197\005\000@\242\030\1855\000\208\141u\212\027|\1318\155\223*\180\211\b\026 :;\027`\018\199\0278*\\n@X\227\026\184\220\169\136\162\131\r\226z\153\r\143)\145\218\004\143XPi|\006\030\139c\001Y\164\028PWU\213S\218\161\211Zh\011\150h\166\002U2z(\001\211\148|\210\162\204w\213^+K\193\207Q\211\196]z0r\132\198\1798\162(%\243\029\004\252L}\253t\229\163\015\158\213U~i&/\169J\248\202\241\225+\163N\171\155\245b\255\180\023\238^\138z\179\222\b\180n\229\b\156\r\005\133\248Y\190A\255\206\171\183\175\nx'M\012\206!\229\219\255P\149[y\169\246\243\152\139\131s\030\254\201)\015\249\143Q\180\182!\225<\192Y8\171\030\003\014\176V\019\223n\221\135\243m]\143\014R\1408\194\208\1948W\140F\247\025'\216\155\002\202\155k;n?\134\211\132\127h\202\157\011\210L\143\160\211\165\200\127R\233z\027\238\225R\177\238\002\000\000" + let d_0fdc0eeaf87b75b6c50e285b375f4e09 = "border-collapse: collapse;\n border-spacing: 0;\n}\n\n*, *:before, *:after {\n box-sizing: border-box;\n}\n\nhtml {\n font-size: 15px;\n scroll-behavior: smooth;\n}\n\nbody {\n text-align: left;\n background: #FFFFFF;\n color: var(--color);\n background-color: var(--main-background);\n font-family: \"Noticia Text\", Georgia, serif;\n line-height: 1.5;\n}\n\nbody {\n margin-left: calc(10vw + 20ex);\n margin-right: 4ex;\n margin-top: 20px;\n margin-bottom: 50px;\n}\n\nbody.odoc {\n max-width: 100ex;\n}\n\nbody.odoc-src {\n margin-right: calc(10vw + 20ex);\n}\n\nheader {\n margin-bottom: 30px;\n}\n\nnav {\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n}\n\n/* Basic markup elements */\n\nb, strong {\n font-weight: bold;\n}\n\ni {\n font-style: italic;\n}\n\nem, i em.odd{\n font-style: italic;\n}\n\nem.odd, i em {\n font-style: normal;\n}\n\nsup {\n vertical-align: super;\n}\n\nsub {\n vertical-align: sub;\n}\n\nsup, sub {\n font-size: 12px;\n line-height: 0;\n margin-left: 0.2ex;\n}\n\nul, ol {\n list-style-position: outside\n}\n\nul>li {\n margin-left: 22px;\n}\n\nol>li {\n margin-left: 27.2px;\n}\n\nli>*:first-child {\n margin-top: 0\n}\n\n/* Text alignements, this should be forbidden. */\n\n.left {\n text-align: left;\n}\n\n.right {\n text-align: right;\n}\n\n.center {\n text-align: center;\n}\n\n/* Links and anchors */\n\na {\n text-decoration: none;\n color: var(--link-color);\n}\n\n.odoc-src pre a {\n color: inherit;\n}\n\na:hover {\n box-shadow: 0 1px 0 0 var(--link-color);\n}\n\n/* Linked highlight */\n*:target {\n background-color: var(--target-background) !important;\n box-shadow: 0 0px 0 1px var(--target-shadow) !important;\n border-radius: 1px;\n}\n\n*:hover > a.anchor {\n visibility: visible;\n}\n\na.anchor:before {\n content: \"#\";\n}\n\na.anchor:hover {\n box-shadow: none;\n text-decoration: none;\n color: var(--anchor-hover);\n}\n\na.anchor {\n visibility: hidden;\n position: absolute;\n /* top: 0px; */\n /* margin-left: -3ex; */\n margin-left: -1.3em;\n font-weight: normal;\n font-style: normal;\n padding-right: 0.4em;\n padding-left: 0.4em;\n /* To remain selectable */\n color: var(--anchor-color);\n}\n\n.spec > a.anchor {\n margin-left: -2.3em;\n padding-right: 0.9em;\n}\n\n.xref-unresolved {\n color: #2C94BD;\n}\n.xref-unresolved:hover {\n box-shadow: 0 1px 0 0 var(--xref-shadow);\n}\n\n/* Source links float inside preformated text or headings. */\na.source_link {\n float: right;\n color: var(--source-color);\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n font-size: initial;\n}\n\n/* Section and document divisions.\n Until at least 4.03 many of the modules of the stdlib start at .h7,\n we restart the sequence there like h2 */\n\nh1, h2, h3, h4, h5, h6, .h7, .h8, .h9, .h10 {\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n font-weight: 400;\n padding-top: 0.1em;\n line-height: 1.2;\n overflow-wrap: break-word;\n}\n\nh1 {\n font-weight: 500;\n font-size: 2.441em;\n}\n\nh1 {\n font-weight: 500;\n font-size: 1.953em;\n box-shadow: 0 1px 0 0 var(--header-shadow);\n}\n\nh2 {\n font-size: 1.563em;\n}\n\nh3 {\n font-size: 1.25em;\n}\n\nsmall, .font_small {\n font-size: 0.8em;\n}\n\nh1 code, h1 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh2 code, h2 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh3 code, h3 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh3 code, h3 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh4 {\n font-size: 1.12em;\n}\n\n/* Comment delimiters, hidden but accessible to screen readers and \n selected for copy/pasting */\n\n/* Taken from bootstrap */\n/* See also https://stackoverflow.com/a/27769435/4220738 */\n.comment-delim {\n position: absolute;\n width: 1px;\n height: 1px;\n padding: 0;\n margin: -1px;\n overflow: hidden;\n clip: rect(0, 0, 0, 0);\n white-space: nowrap;\n border: 0;\n}\n\n/* Preformatted and code */\n\ntt, code, pre {\n font-family: \"Fira Mono\", courier;\n font-weight: 400;\n}\n\n.odoc pre {\n padding: 0.1em;\n border: 1px solid var(--pre-border-color);\n border-radius: 5px;\n overflow-x: auto;\n}\n\n.odoc p code,\n.odoc li code {\n background-color: var(--li-code-background);\n color: var(--li-code-color);\n border-radius: 3px;\n padding: 0 0.3ex;\n}\n\np a" + let d_1005d4f63119125aeb03e8a2fa265969 = "ight-p.depth),v=Ke.makeVList({positionType:\"shift\",positionData:-g,children:[{type:\"elem\",elem:f}]},t),b=Ke.makeSpan([\"root\"],[v]);return Ke.makeSpan([\"mord\",\"sqrt\"],[b,p],t)}return Ke.makeSpan([\"mord\",\"sqrt\"],[p],t)},mathmlBuilder:function(e,t){var r=e.body,n=e.index;return n?new Tt.MathNode(\"mroot\",[Rt(r,t),Rt(n,t)]):new Tt.MathNode(\"msqrt\",[Rt(r,t)])}});var xn={display:x.DISPLAY,text:x.TEXT,script:x.SCRIPT,scriptscript:x.SCRIPTSCRIPT};ot({type:\"styling\",names:[\"\\\\displaystyle\",\"\\\\textstyle\",\"\\\\scriptstyle\",\"\\\\scriptscriptstyle\"],props:{numArgs:0,allowedInText:!0,primitive:!0},handler:function(e,t){var r=e.breakOnTokenText,n=e.funcName,a=e.parser,i=a.parseExpression(!0,r),o=n.slice(1,n.length-5);return{type:\"styling\",mode:a.mode,style:o,body:i}},htmlBuilder:function(e,t){var r=xn[e.style],n=t.havingStyle(r).withFont(\"\");return bn(e.body,n,t)},mathmlBuilder:function(e,t){var r=xn[e.style],n=t.havingStyle(r),a=Nt(e.body,n),i=new Tt.MathNode(\"mstyle\",a),o={display:[\"0\",\"true\"],text:[\"0\",\"false\"],script:[\"1\",\"false\"],scriptscript:[\"2\",\"false\"]}[e.style];return i.setAttribute(\"scriptlevel\",o[0]),i.setAttribute(\"displaystyle\",o[1]),i}});var wn=function(e,t){var r=e.base;return r?\"op\"===r.type?r.limits&&(t.style.size===x.DISPLAY.size||r.alwaysHandleSupSub)?pn:null:\"operatorname\"===r.type?r.alwaysHandleSupSub&&(t.style.size===x.DISPLAY.size||r.limits)?vn:null:\"accent\"===r.type?l.isCharacterBox(r.base)?Wt:null:\"horizBrace\"===r.type&&!e.sub===r.isOver?ln:null:null};st({type:\"supsub\",htmlBuilder:function(e,t){var r=wn(e,t);if(r)return r(e,t);var n,a,i,o=e.base,s=e.sup,h=e.sub,m=wt(o,t),c=t.fontMetrics(),u=0,p=0,d=o&&l.isCharacterBox(o);if(s){var f=t.havingStyle(t.style.sup());n=wt(s,f,t),d||(u=m.height-f.fontMetrics().supDrop*f.sizeMultiplier/t.sizeMultiplier)}if(h){var g=t.havingStyle(t.style.sub());a=wt(h,g,t),d||(p=m.depth+g.fontMetrics().subDrop*g.sizeMultiplier/t.sizeMultiplier)}i=t.style===x.DISPLAY?c.sup1:t.style.cramped?c.sup3:c.sup2;var v,b=t.sizeMultiplier,y=V(.5/c.ptPerEm/b),w=null;if(a){var k=e.base&&\"op\"===e.base.type&&e.base.name&&(\"\\\\oiint\"===e.base.name||\"\\\\oiiint\"===e.base.name);(m instanceof Z||k)&&(w=V(-m.italic))}if(n&&a){u=Math.max(u,i,n.depth+.25*c.xHeight),p=Math.max(p,c.sub2);var S=4*c.defaultRuleThickness;if(u-n.depth-(a.height-p)0&&(u+=M,p-=M)}var z=[{type:\"elem\",elem:a,shift:p,marginRight:y,marginLeft:w},{type:\"elem\",elem:n,shift:-u,marginRight:y}];v=Ke.makeVList({positionType:\"individualShift\",children:z},t)}else if(a){p=Math.max(p,c.sub1,a.height-.8*c.xHeight);var A=[{type:\"elem\",elem:a,marginLeft:w,marginRight:y}];v=Ke.makeVList({positionType:\"shift\",positionData:p,children:A},t)}else{if(!n)throw new Error(\"supsub must have either sup or sub.\");u=Math.max(u,i,n.depth+.25*c.xHeight),v=Ke.makeVList({positionType:\"shift\",positionData:-u,children:[{type:\"elem\",elem:n,marginRight:y}]},t)}var T=yt(m,\"right\")||\"mord\";return Ke.makeSpan([T],[m,Ke.makeSpan([\"msupsub\"],[v])],t)},mathmlBuilder:function(e,t){var r,n=!1;e.base&&\"horizBrace\"===e.base.type&&!!e.sup===e.base.isOver&&(n=!0,r=e.base.isOver),!e.base||\"op\"!==e.base.type&&\"operatorname\"!==e.base.type||(e.base.parentIsSupSub=!0);var a,i=[Rt(e.base,t)];if(e.sub&&i.push(Rt(e.sub,t)),e.sup&&i.push(Rt(e.sup,t)),n)a=r?\"mover\":\"munder\";else if(e.sub)if(e.sup){var o=e.base;a=o&&\"op\"===o.type&&o.limits&&t.style===x.DISPLAY||o&&\"operatorname\"===o.type&&o.alwaysHandleSupSub&&(t.style===x.DISPLAY||o.limits)?\"munderover\":\"msubsup\"}else{var s=e.base;a=s&&\"op\"===s.type&&s.limits&&(t.style===x.DISPLAY||s.alwaysHandleSupSub)||s&&\"operatorname\"===s.type&&s.alwaysHandleSupSub&&(s.limits||t.style===x.DISPLAY)?\"munder\":\"msub\"}else{var l=e.base;a=l&&\"op\"===l.type&&l.limits&&(t.style===x.DISPLAY||l.alwaysHandleSupSub)||l&&\"operatorname\"===l.type&&l.alwaysHandleSupSub&&(l.limits||t.style===x.DISPLAY)?\"mover\":\"msup\"}return new Tt.MathNode(a,i)}}),st({type:\"atom\",htmlBuilder:function(e,t){return Ke.mathsym(e.text,e.mode,t,[\"m\"+e.family])},mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mo\",[Bt(e.text,e.mode)]);if(\"b" let d_105a9e030400f28a404c6badd930fe01 = "[\"mord\",\"accentunder\"],[i],t)},mathmlBuilder:function(e,t){var r=Vt(e.label),n=new Tt.MathNode(\"munder\",[Rt(e.base,t),r]);return n.setAttribute(\"accentunder\",\"true\"),n}});var $t=function(e){var t=new Tt.MathNode(\"mpadded\",e?[e]:[]);return t.setAttribute(\"width\",\"+0.6em\"),t.setAttribute(\"lspace\",\"0.3em\"),t};ot({type:\"xArrow\",names:[\"\\\\xleftarrow\",\"\\\\xrightarrow\",\"\\\\xLeftarrow\",\"\\\\xRightarrow\",\"\\\\xleftrightarrow\",\"\\\\xLeftrightarrow\",\"\\\\xhookleftarrow\",\"\\\\xhookrightarrow\",\"\\\\xmapsto\",\"\\\\xrightharpoondown\",\"\\\\xrightharpoonup\",\"\\\\xleftharpoondown\",\"\\\\xleftharpoonup\",\"\\\\xrightleftharpoons\",\"\\\\xleftrightharpoons\",\"\\\\xlongequal\",\"\\\\xtwoheadrightarrow\",\"\\\\xtwoheadleftarrow\",\"\\\\xtofrom\",\"\\\\xrightleftarrows\",\"\\\\xrightequilibrium\",\"\\\\xleftequilibrium\",\"\\\\\\\\cdrightarrow\",\"\\\\\\\\cdleftarrow\",\"\\\\\\\\cdlongequal\"],props:{numArgs:1,numOptionalArgs:1},handler:function(e,t,r){var n=e.parser,a=e.funcName;return{type:\"xArrow\",mode:n.mode,label:a,body:t[0],below:r[0]}},htmlBuilder:function(e,t){var r,n=t.style,a=t.havingStyle(n.sup()),i=Ke.wrapFragment(wt(e.body,a,t),t),o=\"\\\\x\"===e.label.slice(0,2)?\"x\":\"cd\";i.classes.push(o+\"-arrow-pad\"),e.below&&(a=t.havingStyle(n.sub()),(r=Ke.wrapFragment(wt(e.below,a,t),t)).classes.push(o+\"-arrow-pad\"));var s,l=Gt(e,t),h=-t.fontMetrics().axisHeight+.5*l.height,m=-t.fontMetrics().axisHeight-.5*l.height-.111;if((i.depth>.25||\"\\\\xleftequilibrium\"===e.label)&&(m-=i.depth),r){var c=-t.fontMetrics().axisHeight+r.height+.5*l.height+.111;s=Ke.makeVList({positionType:\"individualShift\",children:[{type:\"elem\",elem:i,shift:m},{type:\"elem\",elem:l,shift:h},{type:\"elem\",elem:r,shift:c}]},t)}else s=Ke.makeVList({positionType:\"individualShift\",children:[{type:\"elem\",elem:i,shift:m},{type:\"elem\",elem:l,shift:h}]},t);return s.children[0].children[0].children[1].classes.push(\"svg-align\"),Ke.makeSpan([\"mrel\",\"x-arrow\"],[s],t)},mathmlBuilder:function(e,t){var r,n=Vt(e.label);if(n.setAttribute(\"minsize\",\"x\"===e.label.charAt(0)?\"1.75em\":\"3.0em\"),e.body){var a=$t(Rt(e.body,t));if(e.below){var i=$t(Rt(e.below,t));r=new Tt.MathNode(\"munderover\",[n,i,a])}else r=new Tt.MathNode(\"mover\",[n,a])}else if(e.below){var o=$t(Rt(e.below,t));r=new Tt.MathNode(\"munder\",[n,o])}else r=$t(),r=new Tt.MathNode(\"mover\",[n,r]);return r}});var Zt={\">\":\"\\\\\\\\cdrightarrow\",\"<\":\"\\\\\\\\cdleftarrow\",\"=\":\"\\\\\\\\cdlongequal\",A:\"\\\\uparrow\",V:\"\\\\downarrow\",\"|\":\"\\\\Vert\",\".\":\"no arrow\"},Kt=function(e){return\"textord\"===e.type&&\"@\"===e.text};function Jt(e,t,r){var n=Zt[e];switch(n){case\"\\\\\\\\cdrightarrow\":case\"\\\\\\\\cdleftarrow\":return r.callFunction(n,[t[0]],[t[1]]);case\"\\\\uparrow\":case\"\\\\downarrow\":var a={type:\"atom\",text:n,mode:\"math\",family:\"rel\"},i={type:\"ordgroup\",mode:\"math\",body:[r.callFunction(\"\\\\\\\\cdleft\",[t[0]],[]),r.callFunction(\"\\\\Big\",[a],[]),r.callFunction(\"\\\\\\\\cdright\",[t[1]],[])]};return r.callFunction(\"\\\\\\\\cdparent\",[i],[]);case\"\\\\\\\\cdlongequal\":return r.callFunction(\"\\\\\\\\cdlongequal\",[],[]);case\"\\\\Vert\":return r.callFunction(\"\\\\Big\",[{type:\"textord\",text:\"\\\\Vert\",mode:\"math\"}],[]);default:return{type:\"textord\",text:\" \",mode:\"math\"}}}ot({type:\"cdlabel\",names:[\"\\\\\\\\cdleft\",\"\\\\\\\\cdright\"],props:{numArgs:1},handler:function(e,t){var r=e.parser,n=e.funcName;return{type:\"cdlabel\",mode:r.mode,side:n.slice(4),label:t[0]}},htmlBuilder:function(e,t){var r=t.havingStyle(t.style.sup()),n=Ke.wrapFragment(wt(e.label,r,t),t);return n.classes.push(\"cd-label-\"+e.side),n.style.bottom=V(.8-n.depth),n.height=0,n.depth=0,n},mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mrow\",[Rt(e.label,t)]);return(r=new Tt.MathNode(\"mpadded\",[r])).setAttribute(\"width\",\"0\"),\"left\"===e.side&&r.setAttribute(\"lspace\",\"-1width\"),r.setAttribute(\"voffset\",\"0.7em\"),(r=new Tt.MathNode(\"mstyle\",[r])).setAttribute(\"displaystyle\",\"false\"),r.setAttribute(\"scriptlevel\",\"1\"),r}}),ot({type:\"cdlabelparent\",names:[\"\\\\\\\\cdparent\"],props:{numArgs:1},handler:function(e,t){return{type:\"cdlabelparent\",mode:e.parser.mode,fragment:t[0]}},htmlBuilder:function(e,t){var r=Ke.wrapFragment(wt(e.fragment,t),t);return r.classes.push(\"cd-vert-arrow\"),r},mathmlBuilder:function(e,t){return new Tt.MathNode(\"mrow\",[Rt(e.frag" @@ -50,8 +52,6 @@ module Internal = struct let d_23f18044ca054da68359124a0e246b96 = "x\138\135\011\212z\199\183\220\149Y}w/\r@\252\019\012N4\239\132Z\206JC\179\183\228\133\137g\202d\232i\151\197\2347v\231\149.\132\157?\235\141\025\231\241\133_J\006\007\237\173\249\148\244\190&\2013\189\157\229\015\244\144\238\173\232q\020\136\130W\229\202\213\1613\012\025\139\218\175\186\241\156.\t\200\127\218V}\153\139\162\184\128d\180\197\205\\:\221 \180\191\224\002\023\237l/\159\237\025\231\197g\237v\\\143\139o\01627\231tq\155\019\235n\012\171^k\249\227:0\218\128\149\171\133\012\019\255k\181\157\174$Z\129\025\149\003A\223\218\156'\248J\143\243\029\225\245'\133\153\179\027\229\011\179J\155:}\174\b\011\194\023\154\166\147\019\2315\144p\178V\189l~\160\166\004\023f\181\176\030\014o?u\213m\015\153\027\194\234\203\225G\029\223\017\016\006BYK \130k\183\\!\\lv\156\235\164u\138\152\189\244|\201\137\140\224\237\222\144\208\129\180a\221&B\207\183y\249\214\198?6\236\210c\019\252\209B4\162\226|Fe\228\003\252\171\188\135\199\163\129G\012U\152`SA\148M\192\t)\138Y\254LF\242\242\b\146\171s\012\ro\20811#\179\220;DPO]:\td\180\162\"\207\019\192\213\2050\016Xr\150F\225H^a\228\172\138\140\t@eAo\147\006&.\2112\020\175j\147:\228\n\176\151Lp\217]\022Gb\227~\147\242\254E\241G\017\191)\158H\225\136*\133{\145\2491\248x\201\224=\150\139\253\"5}\235\224K\n_\214^\152\208\151s\193G\186?\029^\198\146\019\021\015*|\242\250\233\153\020\185\166\191$e/\231\146}\212\245\169|\171\251E\216a/.\236\239@\173\207$\220\164m9\169L\241\138\n\015\252\255\016uJq\018\205\247\156ST\2101\171*\145O\171\182\023\244\019i\204t\024\156\130\213\170\168\017\145\016\169\236\" \227\nj\221F\185\1966\247\131r\"\180\183\210Y\189Bq\176Y\003\133\216y\130\208X0\187\186&\159k\026K+i\015HC{\173\251y&bn:\157\193\254K\200\019\228\141\137\022\165\183\180\163\142W\024>\206q\247\022 \251\161rV\176;\150>\225\147!y\177\249*\197\191\169\215\202\1281\0161b\127\250\017\233c G\220R\184\200\157\233,\188F\192\208)\140i\194\029}\181\253\251\0144\134\252<\187\209d|\1354\241\000\1611dY\211)\250-5\235\241*\001i\253\006\133\238r\146A\136`\002\161KiP(}\202\172\006\201\t%\136%\161k\023\241\002d\239K\254g\003\000_bJ\155\000\217\1666\128\005\145\214`\192f\165\127]*\238\152\248'\018\\\227*\015\245\129Rj\142\207y-]\2363\249\012\181\130\240F\194\253(\r\190+\206\241\222\232\141\192\187\159\1445\169\240\016\224\141\150\246\215\222\198>\210\030<\192\030\004\199t\186\150\173\173\187+_k\"p\137\161\176\156\249\024\227\139\254\160\229\132\025\214\131\017\1461%\174R\021\002@\216\245\192\145\006ay!\168\232\250\148\172\141\141\175\246G\b\204\169L\183-Z\209\235\217\237\252xv\";\162\129e\202\031H\0153vB7\136\178\143t\018\143\202\203\027eh\156\196\029\137\179.\2427\164\024\132\031A\218\252\144?\156\129%c\174\247\211\135\015\229\165\211\196\146=\235\144\225\r\196\b\174\182\164\239U\bJ\191B\198-B[9\1474\1395`\197\180;{2c6\153\230\179x\"\193E\199\bd\027\134v\186O\153\019\199\203\1711\006\236\175\159\168\157\211\217\250\219ad\161\024k\127\233\151\225m\243/\218\149\127sB\b\138L\252\157\191\162\253-\163\189\241K\127\163\236\2018\172\028T\199\245\176\240\153\185\216\250\149\1911~8h[QR\252\027\146z\133\180\139\147\220\214j\223\255\205?\165\127\203\001qb\189\240-9\017\207]\153\246\196\255\210\237\220\151\131/\180\193\002E\253B\1824\194\012\189t\021\164\243\211-GK\193\tOx\011\218\165\211?\174\023\229?\168\218\005\022\225G@#6\254*&,OU\1695\253\018\190,]\149\026&\003\198u\245GN#\019\000\014K\204N\028\203\230\210\210 j\199^\239]\177\206\24807\148Y\134\1893\155}\205\r1\027\217\237\181\235\170\244\018W@\178F\218\164\245U\164\027\153\185\171z\202d\021/\031]\241`f|\233\223\159/f\007\134y\143{\247\2472<\152\253\242H\024@x\243\161X\014Nx>\030\222\135\127\194\151\007\030_\156\253E\152\n\020kp6\166\154\229@nq\174>Sc\030\r1\192\223\154\209\189\164\249\r\206t-\135\n\234\1353\217\018\159\167o\240\172f\252\163\134xB\229\026\147\026\254\2317\179\167\156\161\021\149\194g\146!\021\240\183\214U\155\1401\127\196\156\194\176\175d\209\199\154\188\148\169\006\229{\197}\005\219\n\167;vZ\160\030T\236xjD\254\179\164\239)\213\191~A>\188\0282\202\161\152\216\177\157\192NS\\l1ppp\159\200R\004\030E\238\133|\"H\171\217\184\129\173$\138\206W\194\231\154^\144[\150\192}\193%\193\167g\149\253\182\135\148\155\203\209\198q{8\169U}9\018|R!\169\161\239\bm\162\185\224\196\163\235\006\255\153\030w\011'\215\228\029\169\148\1518\167\173\240\236\206$oq\142\239\128e\215\011y\231b\027\028\157\170W\005\1961+\212\236\147.\011\201\194N\157S\240\129\251_A\232\143\248?M\173U\188\234gFo\130\217`\227MS\2268K\213\207\205k\230\151\024H\253\028\"\182\003\245\228n\031\184\0264\208\157o\253\220\250\149\170\187\221\254\b\243(\031\0234\199\209\203\241,\127\137!E\216\220\254K*\240XNS\143\131\143+\247\177\224`\210]\203\140k\227@\173V\248\128\174w\213\239\163\015\145\130\232\186T\163c+L\215\227\021\129\196\183s\164\\G\229C\028\2285\148*\175\205\206\250\167\248\219\215\135\211\198\246\220\234WsB\251F\164\207\251\212\188\214\216/5+\249E\197\188o\140c\197)\197`\002\127\247x\216\240K\"\137F\172\249\025\233Z\179\234{Lr~\165r\197\175\023\1664\178\128\153\152\250\166\188td\tG\243VH0h\194\192\182j\190\148\138\003\197R\"\007\252\177t\000u\016QD\173\031\017\159\206\237\131\250\132\191%0\219\234\"<\220W\215\021\1509f\244Uke2/9J\234\197\0309\238\221V\187\226\026{i\012\206h\"\186!6NWRzz\225lw\218=3\023\018\149<\029\133N:\206\157\174\203*\203i\175V=\n\2266\003\145lQ\144\012N\185\189<\222tjI&\178\158\161\163\022\178\182\137\250\178\225\229\149\019A\191\151\147\007\240X\216\134\166\217?kA\209@\227 \237O\131*\138\230I\188E\254.\220\242f\011q\167>\158\185;\162\130\198\218\002o\218\0117\181.\197[,\176\187\198\207\143z\131\170\0020^\2552\223\142\011\247(\194ix\165\153\247\177CJ\137\1528\146\021\127\001\183\158\231\229\194\161D\161\165a\002U\246\129\012\218\030\"\182#\244\178$/\192\175\242dr$\2060\242,2\197\204\223\r(\244\246ytp\130{\bt\141W\143\134\179\155,T}uS\251]\007:\170\194\178\004GI>\131W\000\158\250\168\137\208e\235G\181\134\152_\024\244\2493\006\251\218An\020\160\183\226\029\224\161J\r\224X\180\233\015\148\164\011V\210\031\216\2327p\246\149\232\206\020\177\176#d\005b{5\142\241\172\178\241=zfK\131P\149\002I[\015EVX&$+\195W\n\227\024\132{\148\134n\173\tv\178t0kSc\133$m\2495b\006\140\203D\244>ye\017|\195\128\201!\156\142\235\205/\162\028~\1966\025\134\016\012\228\006\249\202\152^\196\014;\143\132 e'\023EAM\156,8\b \018f\224\212l\245\030\226Zjy\223\244\162\027\189\004*\242U\028\255P\147nk_\192\201\2485|\166\0306-.o\185\177_^\224\031\128\r\253\137\210={\209\241\167\248\030\173\238\152\014\020v\202\232r\197\181%0\133\029\211\142\193\006-&\142\197b\219\000\166b\171\229?\004\168~L\251\159\162J\178_W\233b\178\226\165C\162\242\244\164\003\180\217\015\200\200\193\127\249y\162(\b\026\018\t\003\238kZg;\229\193y\006\151A\203!\192e\165\160\145\199\245~\148\012x\014\190\149\011\247\247\129&\148\211\194\011Y\027\178F\214\132\174\22909,]\230\031peUHm@O\224`\148\151\203D\153\141\028\203\202u\002\030V\\\015\234\147!~\026\223\242\029\226\128N\200C\139\215\1285\201\193\171V\203\160\130\207\2242(9\164\129yE\184\150^1\186\210\014\232\027\\\212(\195$i\157D\252Z-\153\011\217\214\152\205\161\151(PG;\161\004\211\216\185\201f[\205\138\020\017!\026\143\"\r\011\234eX\165\006\147\023\201\184\181\023\196\162\241\252\001\1605\255\250\024\185\154\205\168\243\146\211\137\172\177\246X\167\167\012\130\167\r.\139^Y\227\148[\183v\149c\014\222\130\150\239d\229\229\187\254u.\030\185\011\147\011\182\241h\003\149\254:W\186t\006\130Hp[\224XQ\200a\169y>\175\198\1477o\tnv'W\178\180\194%\246\188\1758L\192$\242y\250\231\230n\134DB\225\173\153t\134\b\226\239\214\214\221%\139\165}\007\178\244\209\t\243V\203\186\152\252M\218A}\007\181\191\244\152\239g\170\n\011}\253\030\022\228\220\1319\200(\133\029l\138Pe\243\242m\186\180Pgc\203\236\150\173im\255[q\234\207M\249\199\017\188\226\255u\012&<\143\191)\136\146P\006J\168\004\156H\020\183\020\165\226\213\021\145\205\147\2491\030\167\215\242\159/3d\236\168!:\254\198c\229\239\190\204\161\242W\132>\153\219\255+r~\230H\n\177\133\153\179\015\020X\146\027b\154P\235M\154#Q\136\bJ\236\137\223\"\164-\015Y\155\245\017\252\\R8\1454\159\206H\179\1553\184\248N\025\206\230\200O\022cg\191>\158\185\241~\252\254\253%'\229\028vY\202\226\187\156Akt\020b\255\014\1345\b\161\241\204,*\218*\254\160w\248\229F\182\015\139\244\217\231\161\245\019\016\183k\243\210\151\207a>\136L\195\167\161|^\003\212\146\171m\167\bn\240%\141KB\161\165\161\205\254\252/\249\212jmK.\196k\224\163\127\241\248O\177.is?E\166=\157<~\007ofoZ\190Y\153\001\251\246\206\240\134\130\0248\012\130\006\030_`t\192\223_\136\195\173\254Q\029\210\255\1791)\199\199\176\225\012\t\025y\200Z\165}8\149(\200\143\132\b:!_\253%\194\216\215\170mE\028n\233\130\187\026j\244\162w\197~\1403\003lY\245\019d\238\147!\140\169\164S\014n\187\244\181\255\000\202\1483\253D\132}\bu=K\221z\212\135\247qZ\220\006\133%\190k\234x\248^q\131\003]\024^\226\1389\169\239h\\\149\026\248A4\197\004zu[\150T\208\002bw\254\005y)\192!^\200\r\164|\233J\2111\241\161\159\127\134[\237\\\156\187*=\238\000K\144\136\201\229\1958r\231?\213\172RS\191\220G\245u\190'Bou\158\254\230%\163idV\031~<-\177Y\191\225\194\22468V\t\225D\204\2473\136xD\236\003\163U\213m\029?\255\206\219!I\178\167%c\206\199D\133\241W$\251ws{n\182\1873\233O1\218:\164\253:\155\151M\211\b\242Q\219pf]\155^_\023\023\240y\198\231*Mw'\241\244\253 CPwB\188\250\026\153\019\152\227\198\208\169/\201/\246\192I\001\142\152\176\223C\003O+c\002\206\200\021\179\b\006\015O\162L\188\181L\140\031\190w\248\158\204\165!2\017\177\214\168\194n\221*\194\139\202\138\240O\238\241\199O\219K\022\000\202\2247\242\173\242X\153\204\212\146\016\253\240\220!^\144\138&Xv6W\238\156j\024b\t\211\208\217\018\144\171\227\024UV\031wv\166\239o\185\213|\206\218\140\178n\142\194\223\183\026JH\224\000\023\2319^\219\215Z\225\153h\2370\213\234\185k\132\178YdS\250\003A\1689\132\253yi\176H\161L8\188N\217\155P\246\127f\172\175\153\173u\250\167.N*\142so\157\024{u\152\014\253D\242Jr{\132r\155\204\127R\022\nn\152\003\196G\174\255\214\191,\005\164wt\198\233\255\174\237\001v\019e\158\200\026\148l\nm\151w\236|f\145\2203\n\242j9\006\020'\194r\002,\149\018\168+\166\b\020.\t\154\128V\136D(o\207\201u\2256Jo80\019\249?!\149!\222\178\024}\232\158\028\234\195\175\149b\253\197\215V\236\255$\165$\022\179\179\028\203\220\021\005=\201\177\155\149\178\213-\014u\231\148-\198\029Nk_\019\159\145\143\181\202S\183\002\129\239X\151U\205\\\143;B#T\0140]\002#y\159&'f\164\208\142%\206\202\195\132\017\187\134\136\1390\200\234\216\1776\2080[\1550\220S\149\236\201\012m\221 T\239\250\214y\127\131\251\183l[\137)UZ$\147t\203B\000\171-2e\239\011\212\185\158]-\015\205\202iXx>\176\252\175\178\253\020\135\217\012+u\153\028uP\248\185\212v\186}v~n\255B\197\026|\1664G\165\234:^\191J\219\242\144\012\017 \200\\\175\200c\188n\132\225ZF\000E{-\158\001\152\020\2436\203v\197\b\1319\018e\222n\216\002\185\190\212\0031b){\205\169\2331\1700\230\157\213\172#\187Y+\201\001\133\137\221\179\026v\2181\160\003P^\201k\186\242\206\026\166\155\236\151\251z\178s\153` \143\029f\243cqmh\255\016\\\182J\217\143\235\014e\152\170\223\153\146&\140R\130\230zjo" - let d_26273b7b4624e2875c9e14c7cb14c111 = "e;\n border-spacing: 0;\n}\n\n*, *:before, *:after {\n box-sizing: border-box;\n}\n\nhtml {\n font-size: 15px;\n}\n\nbody {\n text-align: left;\n background: #FFFFFF;\n color: var(--color);\n background-color: var(--main-background);\n}\n\nbody {\n max-width: 100ex;\n margin-left: calc(10vw + 20ex);\n margin-right: 4ex;\n margin-top: 20px;\n margin-bottom: 50px;\n font-family: \"Noticia Text\", Georgia, serif;\n line-height: 1.5;\n}\n\nheader {\n margin-bottom: 30px;\n}\n\nnav {\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n}\n\n/* Basic markup elements */\n\nb, strong {\n font-weight: bold;\n}\n\ni {\n font-style: italic;\n}\n\nem, i em.odd{\n font-style: italic;\n}\n\nem.odd, i em {\n font-style: normal;\n}\n\nsup {\n vertical-align: super;\n}\n\nsub {\n vertical-align: sub;\n}\n\nsup, sub {\n font-size: 12px;\n line-height: 0;\n margin-left: 0.2ex;\n}\n\nul, ol {\n list-style-position: outside\n}\n\nul>li {\n margin-left: 22px;\n}\n\nol>li {\n margin-left: 27.2px;\n}\n\nli>*:first-child {\n margin-top: 0\n}\n\n/* Text alignements, this should be forbidden. */\n\n.left {\n text-align: left;\n}\n\n.right {\n text-align: right;\n}\n\n.center {\n text-align: center;\n}\n\n/* Links and anchors */\n\na {\n text-decoration: none;\n color: var(--link-color);\n}\n\na:hover {\n box-shadow: 0 1px 0 0 var(--link-color);\n}\n\n/* Linked highlight */\n*:target {\n background-color: var(--target-background) !important;\n box-shadow: 0 0px 0 1px var(--target-shadow) !important;\n border-radius: 1px;\n}\n\n*:hover > a.anchor {\n visibility: visible;\n}\n\na.anchor:before {\n content: \"#\";\n}\n\na.anchor:hover {\n box-shadow: none;\n text-decoration: none;\n color: var(--anchor-hover);\n}\n\na.anchor {\n visibility: hidden;\n position: absolute;\n /* top: 0px; */\n /* margin-left: -3ex; */\n margin-left: -1.3em;\n font-weight: normal;\n font-style: normal;\n padding-right: 0.4em;\n padding-left: 0.4em;\n /* To remain selectable */\n color: var(--anchor-color);\n}\n\n.spec > a.anchor {\n margin-left: -2.3em;\n padding-right: 0.9em;\n}\n\n.xref-unresolved {\n color: #2C94BD;\n}\n.xref-unresolved:hover {\n box-shadow: 0 1px 0 0 var(--xref-shadow);\n}\n\n/* Section and document divisions.\n Until at least 4.03 many of the modules of the stdlib start at .h7,\n we restart the sequence there like h2 */\n\nh1, h2, h3, h4, h5, h6, .h7, .h8, .h9, .h10 {\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n font-weight: 400;\n padding-top: 0.1em;\n line-height: 1.2;\n overflow-wrap: break-word;\n}\n\nh1 {\n font-weight: 500;\n font-size: 2.441em;\n}\n\nh1 {\n font-weight: 500;\n font-size: 1.953em;\n box-shadow: 0 1px 0 0 var(--header-shadow);\n}\n\nh2 {\n font-size: 1.563em;\n}\n\nh3 {\n font-size: 1.25em;\n}\n\nsmall, .font_small {\n font-size: 0.8em;\n}\n\nh1 code, h1 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh2 code, h2 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh3 code, h3 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh3 code, h3 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh4 {\n font-size: 1.12em;\n}\n\n/* Comment delimiters, hidden but accessible to screen readers and \n selected for copy/pasting */\n\n/* Taken from bootstrap */\n/* See also https://stackoverflow.com/a/27769435/4220738 */\n.comment-delim {\n position: absolute;\n width: 1px;\n height: 1px;\n padding: 0;\n margin: -1px;\n overflow: hidden;\n clip: rect(0, 0, 0, 0);\n white-space: nowrap;\n border: 0;\n}\n\n/* Preformatted and code */\n\ntt, code, pre {\n font-family: \"Fira Mono\", courier;\n font-weight: 400;\n}\n\npre {\n padding: 0.1em;\n border: 1px solid var(--pre-border-color);\n border-radius: 5px;\n overflow-x: auto;\n}\n\np code,\nli code {\n background-color: var(--li-code-background);\n color: var(--li-code-color);\n border-radius: 3px;\n padding: 0 0.3ex;\n}\n\np a > code {\n color: var(--link-color);\n}\n\ncode {\n white-space: pre-wrap;\n}\n\n/* Code blocks (e.g. Examples) */\n\npre code {\n font-size: 0.893rem;\n}\n\n/* Code lexemes */\n\n.keyword {\n font-weight: 500;\n}\n\n.arrow { white-space: nowrap }\n\n/* Module member specification */\n\n.spec {\n background-color: var(--spec-summary-background);\n border-radius: 3px;\n border-left: 4px solid var(--sp" - let d_2a97d5e4df362b2779e0824fb8c2c024 = "c\130\143~[\007;\175\012Z\218\175=\t\023\248\182\251wT8}\177\229\219\2314\245\157\188\017n n\191\140\170\171FVH\150r\224\231\152jC\137\012\246\238\234\227\231\173\149\172g[\017\200[\159\183\174\227y\194U\242\177\t\141\230R\210\160\232\002Z\221\243\243\207\b\243\250\127\202\2491\251f\015h\204b\187\209\159\232\018\177\243\239\129\031\147\201\180s\247\218\166M\029M\029\"!\173\022\253OK&\017Ft~\131z\222\024\2529x\134\246?j\146l\158\180I6i\015\228\029\212%\147\132m\165\029\019\152w.\192\017\015\239O*s\223\028%\205&(\019]/\163\241\021L\015\211\171\213&\172+\150\196\218\206\195w\159\217>>\148\182;@Wc\166\241>E\168v\r v\182\005S\214V\138\139\219}!\016\001\b:\238Cz\2210\150C\" TX\214De\234\242\145\023\151A\132\000l|g\203\r\153\n\2334\181k\255\130\rQ\015\2223\170\158\181\145:Y\191%\252F\139v\247\212\2150\229\174\201\148\147\204\161\176\198\191\rt\214\141\156:]/7\151\025\243\214\199\243E\153\237rk\1711`t\024\028\020t\207\\hv%\138\219\024\219\253\186XuZ\2293t\212\171\229\2340\007\003\198\143\144\209\128\029<\232o.\186\031\182\142\248^\230\024\219\248C\162\001u\212\230\026\156\023\213\166)9O\b\214N!\131\017\026nech\226\145\230\156\002:\247\t\137&^V\175\012-\175\011\029\248\147\175;}+\175\182M\190\135\022\1691\\\136\215t\149\212\235\236\211\2472\221\148\239\231O7k\015\163\003\136\162G\163i\2201T/R\139\198\133#\028T\\\140\212\127\236\233\180\227\184\158\200FD\127h\186\215\029\173R\158\134\146\b\132.W\212\171\248\157\163\224\235\175\029\2074>\194N\191\169q(<\029\154F\193\216\184 /\128\173\185+R\027je\230\220\191jm\179SQxT@'~q\235\159\183\186\240\215\230\241,\130\202\164(\156c\252\004\161\194\0024\145)\026\029\029\011\183k\181\232\133i\183;<\208\187 \020\208\188jdZ\136\163T\141\172\136I\018\171/)\143\195r\253\1294\133}\143\210\228+\222\142\213j\0164\026<\238_\024\227\208\140\207\204!.\144<\151Q;\138\023\252\229\206\017\021\030\228{\139\139!Xvk\234]\147\141\216\137#\245\025\012kC\156\028\214\249\132\172\022Q`\206\n\235\200t\237\018n\019Y\240M}\190\018\003\130s\218\246c\190M\173v\189\030Z\186k\230\143\221\146YI\163\164%5\228*-\025\006\196\014\211\236\166\131m\029\196\135?\255Q\221m\b\192^]H\031\226\204\015\134\186\215\193\151\159C\027\223WZ\217\134dq3\132\205\011|\241\230\238\233\233\127\215\205\029#\134o\"\163\017\199\173\217\242\195D\179\128#\175F\021C\202\128&\158X\255@+\180\193K\206\129?Lt\001\151\244S,\006\169\017h2\255-g\015\238\178D\201\130a\225P\241\187\196\212\029\221\151/C\228\245\213\214.\005\203\016\211\141\163{\239E-\246\161\153\175\191>\t&\161\140\168\248+\127}\024\127\212\029\177L\02938/\173\254rwA\001\002\024\\\177\247\236\185l\138\201{\253/\226#?\191\029u\161}\251 \234z\004\131\220\020@]\b\234\0039{\128\1532\155\169\222%\151N\166j\197\142\199\187\242\132\159d\255\141/\150\182\230J\2058\007-T\203)\157\015\194\215o>j\139\135\185oN>n\136\018\199o\198\250!\137G\239\t\239\215\139\230\239\253\004\2309\176\141+/R\231\172\217\154\131\166\190\181\249\245\197\152\023\141\178\011\028\230\184)A\220,\002\019\243\224\213+\208l[}\025\\-[\216\168\203\147\238K\198\019\145\240\244\143\196\183'\022\183\235\227\2188\007\022\020\232}\197~\162\247\239\154\250x\rSF\011\227\244\242#_\b\011\253\021\171\n\235\240\127\127\246\186\137\151\156\007\183'\167\003B|\160\232\001\171h1\228+\"\207,\n\025\012pb\186$\017\014\160W\234\223\166R\146\016n=\205F{~\017\030sw\223\005\150\205\224\160\001\130\157\252\166c\232\204e4o.\248\161F\133\tg\154\030\174\127D\167\127\212\023PP\150\t\022l=\176\160]\219\166\138.]V'sKj\213\177\181\220\202\249\255\197\202\255\204\237\\\185\175E\023Uo^)\215\169\196\014A\227\233\223B\195\203\202\242\026\155\203JKZ\195\133\003{\025}\156\156m\199n\237\191r\025zCO\015`Z\158j\228\180\170\031\199\194\167\016\180\151b.\206M\2061\242\130|\1372\135\128\213o\214,.\157\179\149\182\255\002q\174\005r\026\161T\138\192\134\005\210\220\188\163#\240>\152\205\244c\240\190\181\165\128\029G8\206\018\188\164(6W\230+\225\250\245\000\249h?3\179\232Y\136\237\161\024\237%\002\203Z1\129\223iqX\007\bG\159\253\238\127}\223\254\194FF\234l`y7\250\191\016\022\019\216x\231\237G\192}M\027\1556A\018n\203\158g1Cs\201\188\239\136\175\1809T\201#\226\220V\135D\181\242\152\245G\245\021\128\006\208\185P\015\179Y\214p\228\r\014Y\240\196\181G\2197\167wv;+\023\159\147w\170\210\140\155\254\162\202\128\175T\160'.\012\186\143\180\003d6#t\232\016\014\157S&\031C\235,k\200n\250\178\181\215%;\227\163\225\b\030\222a6CL\208\141\177Q\012\005\233}\241w\028b\245\131\226\240\2389\025V\222\022\184\205\207\234j\161\185p\142\242\250\146\177f*T\028\148\031\152^b\251>\023\201\028\208\227\001\139\132\230N>\173\001\002~/\004\206\206=\146\203\218c\147b\201\215\202\177\0234\200f\203\156\178\169Xaf\168`8$\149\153M@4&\217X\242O\006\131\236p\209C\166\207!\177\251\140s\140\211\198k+\\\162\254\245\241\171\2296\196\n@\226PG\245{\242m\225\176\219\215\195\234\228@~/@]\196\029?\186;B\001\193\021gVOBs\195l\205\029\206\238\175`\230\165\208?\136\147\128\2418\192 \"\161\160\164Q\228\157X\144\191\244\185S+h\163\188\142\149q\161g\163\180)2\250\136\197\169\127\231y|\138E\142\209\227\144U'D\255\160\149\005eW\184\220@\138\168\224>\224\225\1456\191\252\140\222R\168\216\236\151\133\247Q!)\149\179\239NsCNga\233\007\237\247~\192\">O\238\158u\190\251\227a8\221\004\031\196w\r,\217_\229\177\200\016YtW\139\021\002\154\219\1713]A-s\1895\213PW\206\199 \187\131\158N\248+\rj\169 \011\146\012\163\244\166\027<\1330tY@\131Dd@\145\135\137* \230f\137TL$A\133\140M@h\185Z$\225@D\0228\162\134\197\213,Bo\137\152\131q\tj{W\024\169\192\201\130\t\215\157e\022-\031`\185W\137\134\002&o\001\019\184x\216A\233\173/\0183{;\203\249\148^b\017\006\172\215\189\165Er\030]\191\162\132\162\157\005\012\168\020\226\218\005\\\148r\218p\168\002d4go\"|Zd\144J\232\184%\206DR\186Z&\208\208\165\198\150\175k\020l\tQ\134D\006&K\024\005\232\200\017\179q\153?\145\1505\180w\014\014P\210\172WZ92\186\161@\192\207u\216d\151b9\179\183V\205\1618-<\235\245\161L\186\177\134oW\228\210\012.\131\134\147{\011\025dX\202\0041F\224\14426\022\202\199\142-(\"\018{g%\006f\242I\208\144(\161\138T \242\144\168\195\029\028\135XdBN\160\166\183\144IA\186\128Cp\138$\144N\000v\155U\178\128S\221\190L\132\002 4\221\203\229\021(\225\210M1\022\1330\172x_\143f7\169\179\169\192\137\129*\2155R>\147\138a\018b\030\147+\152\241h\245a\167]F\018\195\234\169\133\\<\030G\204BL\000\243\2322Q\022:]\012\000\001X\189P?~\024\127u\006\171\234W\n\011\251\002\000\000\022\171\247>\228\174\243\255\1339\129\219\208\247\000\000\n@\000x\"\025\169\197\1605\228r\001\015\158\168\185d.\002\127\001K\232\132\017\240WVX\011F\224/`5\230\004\205\020\150e?\138~\003~(\004\015\192\213`\000\019\164G\246`40\172\145\2188\177R\210\154\t\145\253-\171\208\002\203\2525C\176\003n\165\145\016\251a\142\000FK\177o\129\179h7\152_@\030\210GB\203\192b\244\202X\168\t$Q9HF\150\160\199@2\147\230\136f@\215<\177R\208\140\r\129tA\146\246\001\152\023u\187pM6=\176\163\147\224(\186\000V\254\162\248 \150\224A\194\196c\222\129\186A)\148\003M\220\255\031\246\011x@c\182\015A5\"\129:x\031\168\2030\168\251\161E7\165\015\219\130\239A\bf\253\127@|\t\194Ca,\023\004\233\200\007\189D\145\181\000Lzc\151\001%\028\004\0259\177\021>\015\134\209i0L\025\\\213.\131\188\024{\0183*U?F\000r\224} #\225\214D\222\206\224\030'\180\131\207l\192[P\b^F\031\193\021\028.\204^\183\159\234\004Z\140\006&Q76\170E\228J\164T#g)\\\012OS\189\1970\246\005\176\236?\188\026\253\005r\193\234\227`\200b0\023\144FE\000\128l\176y\246\019\202\006\029,%R\205\129\129\011U\234v\b\024\006I\029\026\134\208=4\012\019\246\2200\156\190\236a$\174<\233\196\2440\1984\210\154K\202d\155\127\193f\027\181\192\028\131\250\r\152 S\164\155\134j\022&\164\151+n\137\025\226e\189\202\228J\196`\150L\214\006\204\164d\190\236\198\2455\169\161\217o\181\t\251\135\200\025\153\172\166\002\162\007}\210\160>]&a\015c%\243\200\204\030\178\189;\178LT\198\172\134\237Q|\020\2344\141\2163\199\153H\131\000\251\200\228\001\231\2002\162g\127\210^>\1438\153\219Y\0153\147)d\189,ZP\152\234\245F}j\bd\134\153\160\190\030G\135lPX\183|D&c^\"\131:\"\176\011OUC\1962\194\186S|\b\021\189\002m\127! \163\133\024\145>\174\027\005\146\201D!\134\1329\189\208\207\254F\245|\194\190\n\178\180\163\255\175d1e\241\207\159\188\127\129\250\206\133\130\138&\011\029\003\019\011\027\007\023\015\159\128\144H\182\028\185\196\242HH\201((\169\168\021(TDCKG\175\152\129\145\137\0183\011+\155\018v\165\202\148\171P\169J\181\026\014\016\130\017\020\195\t\146\162\025\150\227\005Q\146\021U\211\r\211\178\029\127\200kVz\207\155a\138>\012omSr\203\180\183\189\031\185\163\179\171\187\167\183\209\215\031\225\146\203\174\185\238\138\171\005\147\231\142\012\154LN\147\219\213b-m\231.\223\218\025\239\"\2493\179fe\006\155\179\150\219H\141\003\189\019\025\"\172e\239\234\201\160\150A\020\027$5\012\246\027\155k\026\029\031\028\158=\130\197\006\0061\226\220\027\174\211Y\014\234n\128\167\018-\023!\220\146\186\000\191d\182\027\189\b\200.\204\179\"\154 ;\176\244\1338_K\203b\222G\157\237Ld\163\206\238\200\148&\146T\002\144\213\0078\198\028k\188\001\024\209bQ\137\135\189S:\030Zr\016\011E\193k\n\165x\166\161\166\020\230K\220R\238\t\166\253\187t\031\206\192K\249/$\249\198\148\172\218k8_]\250\245]\234\2143R\222m^\000\231b]\194\000\224\007>\006\128m\241\208\000\021\024|\014\193\157y\021\240\253X\190\249g\199Dn\131\029\192\139\156\215 d?\163\174\190\243\215<\176\243\006\001\000\250\1713\000 a\138\027!I\023\005z=\018\245GU\022\146\246\166R6\143z\205\150Xa\218\253f\2049\023\170\210\011\248B=W\239\212\251m_\142\178\203\179y>/\2294\247UJ*H\205\255\204\233\179\011\207\211(\224\243\231\127\171\222k{O\153\228\158J\2008R\253o\186\255?\190}\235\163\015\223\187xpW\127\207\240\255\154^\191{\234-J\158\251\238\186\227\150\155n\244\217\160\r\1701\220\169qU\\\237\017\176$\227f\255\213\171\014\014Ht\001\150\1640C\186\204\255\185m\248\\\226\181\188\211\255\230\250\254\011\163d\201\006\130J[;`\249\002\240\163\203\196\238~Y\186\015\153\240\226\167\136\149\207\132=\\\226\130\131\246N\014\148\214\004\181\004~\169\006\000\001\1917\025!\144\172\211\1400D\139\206\136\000\2531\178ukdJJ\b\239M\130\183J\147L\217O\152;G \215\b\179\012=\209\235\163\001\238:zC\221\226\129\174\137\031\248\219c\223\003\156qb\006I\146\164\011\tA\196\030\186A\150\224\193\016\026\135\004\tZ\164\237H&4\174\174B\015^\221 Z~\r\t\137\199\186\171\137\245V\019q\183\245\219V\198\171X\163\140\\\251\146wf\204x\159\146\241\226\144\138H\232\153\000\1947Z\"\014\217A\132\174\198`\138\184%\156\136-\249@&\235e\246;ICi\154w\159b\138\176\147\203\142\160\220\018\020u\148\180+* \241\137\241g\225B(]k\248\130!m\1731}p\132\130\005\233\145[D\202(\198ed\0005\136z\232A&3\249\2004C\220\140\210\186>Z3b\166\166\136\194J\204\185\1931\168\170*\209\225\185!\225Zwd\2044\172>\017\201\255\153q$\199\208D\180lZ\191\161\194\150\179\226\180\003\189w\022ee\019A\140\20622A\022'\003\128\199\024\225\177,3\002\130\229T\129\240|J\232\155\214h\179L1@\210x>\187\011T\218\242\158\213\240VW\004}u\220\019\027\003kS\252\181y\173A\1318\169 R\185\012\170\160\144TWD\221\163\142\134\134\222\208\012\168Fc:\201Cz\141\021\"\226E\181\234\127nx\180:\141\0150\200X\">(\019s\204[\023$\152\233]+\209\238\181\206(@\130\187\158\029-\145\140B\140\t\000\005\\\162\246\236\150\025G\2257\\\174\b]\133D\244\224\012\210+.Pi\143\134F\017=b\1392\205\"\233U\140\229\029\155\208\159\202=%o!G\001\146\140\219\180\203\219\231\186\210\163C2\184\020\t\136\203]Ql\027\017j\134\162p\234X\176\155$\184\192\194z\132v\004D|\145\147\2334\162\190\017\183`\200\136p\166\165\199\251\169\1706\004{\012w\021\235(`K\161\240$\210\140T6\227\215o\002\224\134T\132H\144;@)]n1\002\163\004\014\238X\138\205\160&\223\012yF\184\026\248\243\184\1891\016\141n\140\1401\218#\233\"\019jI\186l\229\214\201\225\019\151Q\134\004\136IF9\019\b\197\017\024)\b\130\148\004E*\194@j\130!\ra\162x\130#-a\141\177BloK\172.\239XAN\232#R\232\144kk(\1459\127\207\154\\bv\254=c$F\028\r\029\199\017j\167\231P\164\232\134u\152\196z\172\216\128\021\027\177b\019Vl\198\138-Xq\002V\156\136\021'a\141\218\129\002\172(%\2223\174\162\148\187R\142'eF\187\191\214s\128)\193\148\153\174\160\000\180\153\029iJ\152\145\164\158}\171\1724GN\254\204L\252Q\239m\133H\205\018#m\215\246\173\211Pu\153&\251\246\168\027\248$\245\232T\140\138\014z~\006\161\144#s\157\td'\224\174Q\245Mf\146;\017z>#i@\129V\246\016\129\159>A\025\211\145\223)2ft\139\016bW[?\019\t\022\2173\228\218 0D\138\237b\220\210Z+\001\246@!\238b\152\0252\018\180}\243u\198,\016\200(\031t\212\127\\\151\222\019W|\228pr\024\237\006\0201\227u\014\217A\228\167\211@\204\012\161\001\182\224I}\239\141=F\245:\169\172U\174+\157A\217j6\017\r\196!i<\205\145\161*{\164\227g\164<(}/d0\244\019\189\233A\161\236Q.-yU\0164\218\021i\194\140\018\178\217\204VA69\220\160G)K!IR\242\028!\195\131I\219\193 Z\004 .!V@\209$>\162\219\0029v\144\144\024\198(EH\138\153x\137'Hv\155\216\b\024\016\028\024\200\173\231\020\225\173L\131ST\216\028\133h\229;\151!\147\031m\2121w\218-\174[\248\017\204\232\233\130\163d\131{ \239\022,\239\189\146\253\226&\173\186\222\241\181\188\016\228\022\164\166w9\237\134\218r\022\133\203\147#I'\133\179\211Cn\169\141\142}\187eM\252\136\253`V\012\022\027\000\179#\1463\248\215\141\140\025\221\226\1361\167\163\025\005\131@\230\155j\177z(\144;\241j\195uMA\129\\fX'\134\144\216\0037\221g7\156\127\022\173\007\131>\128a\015,dFi_\025\166\157\140(\127\012\200\154XD\n;t\030\166\165\0184\241\169\143\011T\"\228\217\000\162[\188\145r\167\205\206Ka\195\"$\000Io0\253\138\020\131\153\127\168$\012d\181\192\017h\162\215R\172\020`\214I_r\198\185f\144\144\198\030\t\242\203\016\014\br\216\142\243I\004\005\138\203\016N\b\241\1699\022\224W8s\004\229\229\b\023\014\228\146\132@\164\"!5\tiH\228\150\031\014\146\014\142Q_\134\240@\144\199v\028&\019\020h.Cx!(\171L8\224\216\224\018\237\229\b\031\014\148\179\128\002_\142\160[9\194w\007\211\031&iw\244\148\2317\157\214\224|a[~\027\156;\194\142\248\137\250iG_\023\142\159\011\244\031\1618\030\134x\194\233\193\147N\143\186\248\003\251\208\018?\212\136\150\186 \180\204\005\161\229#@.+\188\194\153\139W:s\241*g.^-\020h\141\011Bk]\144\180N\148\228\225\245\206<\188\193\153\1357:\243\240&\161@\155]\016\218\226\130\162[m\1679\171\218\152\025L\245\132\194\199\130k\012:\149\174\182\214g\157\193;g\016\227\201\228Dm\147\012 P\255?\129\187\178\165\220\191\233\228\017\128x\002@1\014\238\206 \004\144m0\005\174\174<\130\001\001\229\194\175\024\190-\002.T\164.S\225\1301\148U\155\240,0\240\157f\187S\199\160\214'\155 \141\0119Gdwu\232\249b\169B\209\195\201\23128b\169\136\159/\230)\212\234\018\131B,\146*\213\198\236,\138\153i\145\216\180B\177]\194\023\241\021<\190E\234\144\154\246\131\186\004)\004?7\217\153\"\209g\168\131n\169<\142oL\160\184\193d\171\177(\228J\141\215(\196\148@\205K1\b\244\236\204\028\142\216\169\146H\141\025\146p*W\170\227Y\248\166\204LWr\014\157j1\200d\018\142T*1+H\145Z%\225\024\164R\173\158\135\139\228\201\218\184x]&\157\205gG\203\197\002\185B.W(8\012\014Z\197A\172\003\254\199F\254 t6\157\183\172[ (\230\0158#\147\018\147\018QT\211\171i\233\189\160\\\156\153Y\026\233M;+4\161e\017\134?\007\020\134\205?Cu\236_Oi\220\001U\005j\236\015\219U\217\252T\138\207\175\162T\142\169\015\232\200\019\129\226\031Z%\017\151\031\173\249:\019\222\181#b\201\029m\145\164 \020\218Kq\179\217*\002\132\149\195\214.K1\199\004\145\254\226D\170\242\251\165\n\031\143a^k\222\014h\216\152\003\029@*\026\027\b\253\165\194/\\kA\168\152I^s\012\203\149@(z\160\2090\181\031A\152\208V\132\b\134\nL\218S\027\250\152\212\001\132\152%\236]\015U\024\218)\253=\130\232qB\255!t\162\018\245\172\198\248\028\180D\209\131\132\157\179\233\242\b\148\204d\170\028B\146\162y\139w\234\135S\147\143M\174\148\230\174\190\253pc\247\229\164*\207\180fS\1590Md\233e\197YB\171pC\145i\012F\197\b+y\"\023\n*,\016B\195\014\158\005#\r\012ub\248\016a\183e\219\138\025=\176K\026\166\185Uwu\245\169\018~X\184\139]u\229\216\229\001\"\211\243\208\029\211a/+\185\179\144\170\206t0\006\243\213@.+\007M\1861B\028N0\029\131\164\243\b\0053_\225\238\133gT/\249\172@}0\152\240\250\003\001\245\179b%\169\144\2010I#\205\006\bS\159+\220LopZi\233Jg\243g\162@\031\140\217\158y\151\223\002\132\238q\132\209;\250\140\025\159\135\180)\141\tGD\226S\012\130kwW\149\134\235\169\209\203\n\180\006\132\158\246\170\023\152&\031\243A\249t\195Q\175\195\018\138e\015T,pW\r\017*g\029?\221\141\160\202\208\012U3/\"E\217\r\023\240\141\2108+\1786\213K\031\131\153\192\000\157,\011-\141<\212x\012bo\r\185`\237\015\018\208\031C\177\188\030\236b*c\156\160=uP\026\031\167\224\018\231\199&\183#~\135\169}\001\184w\202\004;\196*\235\173\195!\166\225Cs_Z\156$\140\029\014*g\017\214\021\176\\5\160\176\236\1893\150\212\021\004kqc\167\022~\216\000\193y\222\028'`\149\174)+\128\234\173\253\170\162h\212\228\214\196}\191\031a@\2219\127\229\220\205\166E\132b\160T\251\232\235\180(\211\186\\e\179\132yK,\149\149f\216\150\132\251y\198@\132\167\151\t\003\156L\128\194\216V\179\016\187`\030y\166\217Xe\128J\161\136\242/\182\176:\018\243n\232U\235\148\204\199\027~\236\n\194\002\155dy\228\207\128\187\178*\031\028Q\222\016B\180\139\191\174K\208^\184\022\195`ZGz\003\147IKW;J\201\001\205\188Y\174\209&\157$\na\235\250@\197\237\003\223\"\220n\147\153#W\006\246\148\193\2539\127\249?\149\175\153??\145\170\250\254\000\129\205\148\208\147\139\133S\211XgU\206I\227\195\019\189\232\1777$\245xl\168\254\207\200;\1685\235\216\136,\237\210\204)\022$B\232\182\185\012\159\182_\rd\017E\"\225\229 M\143\202\148\234\223\215\223v\127\242\175\029\141\247\208e\248^\200\228\024\169\178\235\139\197\246\007\165\173M(\252W\195{Aq\207\184\139+4\152^\137C\153;S\146\214T\219\198\242\251\236\133\224\204\025\225\150\2125\240\254O\127\251\196\140l\022Y\228#\171\213-\169^Jv1\157(\227A\147\202=\163\162)dM\255)=\233m\015\020\254\213\2534\151\006\1389\017\158Q~\t)\239\131\222\245\188\134\199\1914\t\202Iky\185\220j\197c\165\0166\2379\200 \152\178\138:\157\224M\007\173\012\178\182Lh\241\181E\236\022\181!B\031>Y\019\243{\185\145\196L\209\\\166\200\161T'\b\172M\024!\143iM&\168\135\201\222w:\160<\027\140\129\187\1520\240\178TO\131\154|\252!\166\176\249\140\129M\bq\224q\136\144\171\199l\\;%\223\247\208\001uwo]LE\148\2385\004u\003\134j\r\249\181\214\179\001\030\164\222\139\232\157\160\"\247g\027\150\005\218\181H\1362\172Y&wg\201'\204\240=\220|04rg\134\167\022\r\234G\238\234\147&5\182\211\248b)\183!F\244\255\174\211\177@(V\170\003\tB\176f'\2169\231\0157\197\208HXy'\004|\158\228\240g\006\243\141/s\156g\177\2264\\\216T\246\208H\177\206-g_\156\139\188\177&\225a\194!\190\221\208\184\254\254\202\255!P\007lz/\188\203\197\199\191\224\146\011\183\152\1403\160\248\015l\204\t\241\000:\222\141\241\227\170\133\147WT\\g\169v\170\002?\189%_\219\252\130\240F" @@ -98,6 +98,8 @@ module Internal = struct let d_5e57240b8ff6745d663ebd2060201199 = "0;d<2;d++){for(var f=!0,g=c+1;g0&&(n.style.minWidth=V(a)),n};function Ut(e,t){if(!e||e.type!==t)throw new Error(\"Expected node of type \"+t+\", but got \"+(e?\"node of type \"+e.type:String(e)));return e}function Yt(e){var t=Xt(e);if(!t)throw new Error(\"Expected node of symbol group type, but got \"+(e?\"node of type \"+e.type:String(e)));return t}function Xt(e){return e&&(\"atom\"===e.type||re.hasOwnProperty(e.type))?e:null}var Wt=function(e,t){var r,n,a;e&&\"supsub\"===e.type?(r=(n=Ut(e.base,\"accent\")).base,e.base=r,a=function(e){if(e instanceof W)return e;throw new Error(\"Expected span but got \"+String(e)+\".\")}(wt(e,t)),e.base=n):r=(n=Ut(e,\"accent\")).base;var i=wt(r,t.havingCrampedStyle()),o=0;if(n.isShifty&&l.isCharacterBox(r)){var s=l.getBaseElem(r);o=ee(wt(s,t.havingCrampedStyle())).skew}var h,m=\"\\\\c\"===n.label,c=m?i.height+i.depth:Math.min(i.height,t.fontMetrics().xHeight);if(n.isStretchy)h=Gt(n,t),h=Ke.makeVList({positionType:\"firstBaseline\",children:[{type:\"elem\",elem:i},{type:\"elem\",elem:h,wrapperClasses:[\"svg-align\"],wrapperStyle:o>0?{width:\"calc(100% - \"+V(2*o)+\")\",marginLeft:V(2*o)}:void 0}]},t);else{var u,p;\"\\\\vec\"===n.label?(u=Ke.staticSvg(\"vec\",t),p=Ke.svgData.vec[1]):((u=ee(u=Ke.makeOrd({mode:n.mode,text:n.label},t,\"textord\"))).italic=0,p=u.width,m&&(c+=u.depth)),h=Ke.makeSpan([\"accent-body\"],[u]);var d=\"\\\\textcircled\"===n.label;d&&(h.classes.push(\"accent-full\"),c=i.height);var f=o;d||(f-=p/2),h.style.left=V(f),\"\\\\textcircled\"===n.label&&(h.style.top=\".2em\"),h=Ke.makeVList({positionType:\"firstBaseline\",children:[{type:\"elem\",elem:i},{type:\"kern\",size:-c},{type:\"elem\",elem:h}]},t)}var g=Ke.makeSpan([\"mord\",\"accent\"],[h],t);return a?(a.children[0]=g,a.height=Math.max(g.height,a.height),a.classes[0]=\"mord\",a):g},_t=function(e,t){var r=e.isStretchy?Vt(e.label):new Tt.MathNode(\"mo\",[Bt(e.label,e.mode)]),n=new Tt.MathNode(\"mover\",[Rt(e.base,t),r]);return n.setAttribute(\"accent\",\"true\"),n},jt=new RegExp([\"\\\\acute\",\"\\\\grave\",\"\\\\ddot\",\"\\\\tilde\",\"\\\\bar\",\"\\\\breve\",\"\\\\check\",\"\\\\hat\",\"\\\\vec\",\"\\\\dot\",\"\\\\mathring\"].map((function(e){return\"\\\\\"+e})).join(\"|\"));ot({type:\"accent\",names:[\"\\\\acute\",\"\\\\grave\",\"\\\\ddot\",\"\\\\tilde\",\"\\\\bar\",\"\\\\breve\",\"\\\\check\",\"\\\\hat\",\"\\\\vec\",\"\\\\dot\",\"\\\\mathring\",\"\\\\widecheck\",\"\\\\widehat\",\"\\\\widetilde\",\"\\\\overrightarrow\",\"\\\\overleftarrow\",\"\\\\Overrightarrow\",\"\\\\overleftrightarrow\",\"\\\\overgroup\",\"\\\\overlinesegment\",\"\\\\overleftharpoon\",\"\\\\overrightharpoon\"],props:{numArgs:1},handler:function(e,t){var r=lt(t[0]),n=!jt.test(e.funcName),a=!n||\"\\\\widehat\"===e.funcName||\"\\\\widetilde\"===e.funcName||\"\\\\widecheck\"===e.funcName;return{type:\"accent\",mode:e.parser.mode,label:e.funcName,isStretchy:n,isShifty:a,base:r}},htmlBuilder:Wt,mathmlBuilder:_t}),ot({type:\"accent\",names:[\"\\\\'\",\"\\\\`\",\"\\\\^\",\"\\\\~\",\"\\\\=\",\"\\\\u\",\"\\\\.\",'\\\\\"',\"\\\\c\",\"\\\\r\",\"\\\\H\",\"\\\\v\",\"\\\\textcircled\"],props:{numArgs:1,allowedInText:!0,allowedInMath:!0,argTypes:[\"primitive\"]},handler:function(e,t){var r=t[0],n=e.parser.mode;return\"math\"===n&&(e.parser.settings.reportNonstrict(\"mathVsTextAccents\",\"LaTeX's accent \"+e.funcName+\" works only in text mode\"),n=\"text\"),{type:\"accent\",mode:n,label:e.funcName,isStretchy:!1,isShifty:!0,base:r}},htmlBuilder:Wt,mathmlBuilder:_t}),ot({type:\"accentUnder\",names:[\"\\\\underleftarrow\",\"\\\\underrightarrow\",\"\\\\underleftrightarrow\",\"\\\\undergroup\",\"\\\\underlinesegment\",\"\\\\utilde\"],props:{numArgs:1},handler:function(e,t){var r=e.parser,n=e.funcName,a=t[0];return{type:\"accentUnder\",mode:r.mode,label:n,base:a}},htmlBuilder:function(e,t){var r=wt(e.base,t),n=Gt(e,t),a=\"\\\\utilde\"===e.label?.12:0,i=Ke.makeVList({positionType:\"top\",positionData:r.height,children:[{type:\"elem\",elem:n,wrapperClasses:[\"svg-align\"]},{type:\"kern\",size:a},{type:\"elem\",elem:r}]},t);return Ke.makeSpan(" let d_6573d83a382edbb1785a8f45c85c3975 = "\197&\159\202(?\2397/\139(\146\186\151I\172\241\191LC\150\031%\141\133\157\220\190\014!\151\129\204\239/\138H\138_\187}f\246\186x\173\252\140\176\002\174gp\133\250\193\168\248v\024.\014\007\137;h\246/\236\180\239\216\194\173\155\191b\r\229Co \193\155\127\161?\222\006\138?&o\221\212\197\134~N\1504<\229\178\174\182\128\241`\165\151l\171%\156\165\\\248\2043\201\17930\183\148p\1807\228\240w\141\007\173W\217\220\167u\227\186+yC3\136\0187(bl{\184K\228q\187\201\170u\179\027\024\181\205uO\185\236\171\173\227\193\202\255\255\227\157\224L\017\006:\219tD6\178\141\179\173>w\166-\224*(~.\027q=\147\206\170\160\174S\021\028,\004\012`\218\132\199\151\024\229\028\166\179\220\2404\13309\127\021^\007\153\005\205L\172\004\244\171\250\181(A\162=Q\150\244\210\011]P\132#kq\253W1\229\007;-Q=(I\160\207\015n\191\n\152\0296>g\2462\238\022\184\187\250N\001\165\002\217\184\219\145\0060/\019\130\230\127]>\197\144S4'\003\222\155J\191um<\151\181\200\005Q\174\205\143\030\183E\167\207r\231\nF\211n\\\005\005!\246\018\137\021\241N\215\187\011\230\141\"V\229\1637\193\213E,\246\162\219\224\150\148k\159\239\011\205\190z\199\003s\135\232\148\246\180\128,\135\003\240\002\197\181g\159\172y\140\031\226\204\195;\196\219\004\213assxVf\194\216\155\017\173\158\247o$\251g\243W\139\255\214\255B\148\139\246\027cN\131\139\227yJ\210\212\153\\`{\016\142\133\151>\204\179W\207X\027\147h7\189\030L\146sxJ6\202\200\205\175\219;\204\166\142\174\026\253\199\023{\023;A\178]\229\140\226\244\001\179\133\031n\207\169\207\149\2327\199\249\180\190\1934n`\157\201\191m\168.\219\221\236.\238kS\\\190\214\187`\241\172G\192\197\219<\133\213Ve5S,\213\243jg\242\207\017?\202i\230\130\028MDG\"\167\184\222\129\173\219-\186]i\249t&\223\147\194\238\158\183\134\255j\234\239\\\206\179\025#\224\162O\211\2197\191\150;2\227\025\231\207\203\004t\238\159\240\"\2112\253I{\195\148\249?\184\018\163>\191:\165\1502\182\242\212\225\006\193\172S\022.=h!\224\195\180x1>\221\247\193\160\255\233\131\240\171\016\171\139\241}\184\002\207>Q\146k\149\218\224\228\192\204\128\237\241\241\127z\235\007\240#R\241\221\249x2\023'\241\003\024BS\019\205x\185g\180\220#\202\202\246hAi\177\189\130\190[\022\1670=\199%\\\127\020\1583\177\003\248\201\222\250\249\248]\177\244\200\0161\169\238\192~\130?f\1596\127\221\229\1308\176\156&\161\137\251\251\212W\231N\134\231\154\193}\135\222c\175\237\r \204\131\248\159\190\189\255\219Nh\232$\129\134R\202A\162\145\195:\222\029\143f\191`\127\2318Dr\189=\138Z\209E\012,j0b\016\252\241\251Z\226\127\155\193'\162\223\140\204\140\193Oa\2449s\005\171\161\197\148\154\167\142R\199\217\244\n\228c\030\022R\001\t,\003fz\011D\2070\149\128DW\142\224\138d\r\029M\166\240\213\0039\243s\0260\138\194B\144-j\182\251.\128\000\004\000\132\191\174\r\242\217\169\222\222\031\252\2428 \130\155\244\012p\255*\245\1791\144\203\158\195\2248.\017\224\030\254\220\213\025S\245\143\145\024\195j\209jC\140\029\248\208\159\196\193\230\241\211\229\0119\164\144Q\240\204[\249\159\232*q\160\217?9#rl\011\216\198\197N\177\216\187\153o\209J\184\134zc\018\238\247\224\002\201j%\214\202'\167+\198u\242E$\173h%9}|\176\249g\177\023u\000\150\255\220\155F=\1381J6,\151h3\216\003`P\235\167\198\141\229\0202\194d\140\205y\181cx\151\147\245\011\192\150\155\195\174\219T\219\200\\;\139\172\"\219\210L\149m\210\177q\029\223\210\rZ\011\140\241\214m\138$\169\200M^XOw\156m>\231\158B\229j\223\161\169\147\178\017\1953\2013\003(j\209\160\030\130 \216\171k\181P\151ymW\180\003g^\186\007\030)\239\236\147\241\\\238O}\195f\254\185=PDyyX(\153f\011l\127#z\147K\129:./\157\nE\193\2321\025\199\242\159I\158\165\188JN\136\"\005\182!@2o\241_\149TJ\148\143\128\236\n\217HA}o\\o}\193'\241\019\153^\165p\175\177\191+m,\213\200\027\183\149\179%\002\132\1816\208\214D\167n\165\200\239\128\252c\025wp\206{%\139\188\0199^6>U\176\023\000\176\250\155\230\186\254\197\141u5\205sE\017\236\150\025+G\135\255k\012x\212\158\168\218\249\17224\029\229uk\231\224\244\217G\242\"\234\2312\252X\014\131\213\182tI=\231.\132\224\184\197\130\019X\181\014Ng`:\134@wS$&\186\219H\2374\201/\238\191\200\195\027+\201\254!V#\150\171\199r1V\251\240\146&N\173,\172\182\1373\0124\002?\022yS\199\1347\006qp\238\\Mmm\141r\173a\160\166\134\208\180\166L\240\248O9\171k\028\\$\215<\192\238\002\154\151\227\011\029\198\217\179\178\173\199\2135k\150\219\173\226Q\215Q\131\235'\148\235s\019i\163\171:;?\186\165\\\251\030{\218\254\189\211\012\186\145;\1742Hw\198\193\137\250\005f\207\185E`/\202.h\205\0308;\161\220\197}/kg\182\020Qs\200\2202G\206W\148\188r\005t\152\134,P\170\014\168\140\190q\160\218\181%Vo\225l\029\151\250\225S\217\211\015\129\219\029L\226\140e\023[\187\215o\001O7\140\217\"\190\233*\209\b\238EJV\251\141\232M\\c\187\2114\197\127\000\nv\156\017\234!\b\218\232\213\251\194\029\224\151o\2314\024\238\223\167bb\168\181\128\161a\142\237\203/5\022\139\2244\174\127w\198\213U\213\212T\209\249\128\161\015\207\029\171\229\174\020\1428\015\209h\1873\".Bg#\233\016\147C\127i\176\207\2336\148%T\030AW\215\001\183K\252`w\131\186\213(R\241N\015\163<\129\002\016\135\t\129d\220\184\012.\189\002\151\\\198\007fr\224\000\190\163\250j\2479pz\220\157\201\024\012\b(\224}\224\r@\004\128\177;\1477U>y|\169sW\r\030\12893o\254\196~\183\169e\212\027h\025\132\151\\\006C\017\136NG\188n\251\136K\001\127\167L\163\159\023\156?]=\211\187\227\243R\224\157\251\025\199\198\1425\236\146\2362\212\214\030q\133\t8?\188\250\015\139\146\202\227\\\246q\229\248qk\162\193\135\127\028\203\184\234\024\255\145{\220\186n,\248\243EV\224\186`\239XP\182u\029\198\229\161\135\223\201\135\183\128\188)\216M\148\1851\206\2301\207\173\223I\215O\165ug\183\142\202\174\217\200Dob\204#\243\206p\184\243\206\028\001\230&l\003\147\179yT\225\221r\214\157\242Q\133g\183\018$\029J_\212\208\020Z\028\030k\181I\151\1327\133\026\022\165C\224\229\140\182p\136=\161'GcK\204\243i\152l\130\205Q\002Ey&\222\025\001\150\198p\228\016\179g\014\141\230+\238\254\173^\160br\187K3\200\238\b\240\242o\192\133A\190V\018/\163\1791\026\204\239\171\202\234\2302U\130\210\132\132\178YJzS\012\232\132\025\211%q\251_\140\179\170\178\2351\004\134`\022\r\130i03_\147\224\213\184\157=\192tN\192\029\249\250\r\155\166\137n]O\n\169F\195\007\161\019A\031\228m\128r\027 \253\206\2193\1841\169\153``\1985W\186C\225\180\179_\250|$2\0303\191\251z\132\139\158\b\157\012)\141<\163\225\029\219\251\193\233\150\235\220\213Pn\003\156\219\000>c\134Tq\232\250\196k\221\198\185\162\185\246\165O\237\1613&\230D\200\253o \024\243\158M\152\025<>-v\215\029|\1370,O\156\171\233\218\189uB\216\143\169\241\239\149\240\214\214\027\189\182Z\222tVt\129\200\173j[\185\174o\237\158\219/\214\146}\177IC=\017\187N\b\166\217c\211\014\139\235f\173\171\208\184#\nD\191\236$\218\231\250jx\253\020\184w\163\197\218\235Lvi\235\1964\154\017\203\019\229\217\232\204\221\006\187a7\139n\021\229\229aF\154|\190\205\206\194\133\220\176rx\140:\151\227\b\141\243\218\002y\134\217\163{Y\236=\134\217\129\188R_Y\130\ru\208\193\253\027i\193\204>2*\166\192\242\173\158\147\154\231\181,Aa\152\2171nj\175\199e*\203\172o(\162\177\247e\150\153<\174\222qS\153\0290\140\022\232\199\\y$m&w\250b\157\133\029\227V3\134\017\181\224\2298\198\234B\223*WU\229\135\179\204{'\015Z\248\236\161\196>k\222\231~)SO\003\157\215hWQzC[\202L\184\235\225\193\173_\145_\189\183\183\247\183TY\234\196\231;7\158\1869_0\255\0265wQ\237\169\255\134oZ\181\188\251S\181`\220\173\213+p\188\252\1636\200\2022\187\019\147\204\159h\249\197\145\132;\163\233\129Hl \b\019\014\188\149\171\1924\210&\147|XPr\213\143\199=\n\196\144M2\189\140\147;\222\185j7\192M\004\145,\1591G_cM\174\204\243YLz{|\014\131\182_\n \239\005{\162y\222\212T\147\211\182\141.\145a\194u7\151\252\201\229\134@\2394\200|\248@\141Y\250\186\207\195\156\179\195\235\213Vl\000\1855H(\158 w\188\158\018\214\018\219\172E\160y_\254\205\163\187o\192\183\138\194\198\030q\003h\207nht4\156\t\028\213pcPI\190\250\214\233L\217q\185\222\000L\214\226\200\205CJh\199%\171\rO\206\134l\129o'3Ta\246\250\254K#\029*zs\203\221h\172\160~N\173\160\249&\031\135m\226\194z\b\137\166A\"P.uO\011\174\135{\196\153)X\243G\249\139\138\231\012\003\201,\143~\255>k\202\140\142jP \016I0\138\167\015~\220k\149\179\b\195\2344\141?\167[?\186\018\181\213\146\185\218\021\001Zz\158?\176|\145\128-4\140p$\178\163S\207B\211\255}\140\233)\140\211]6\n\239\138\002\131s\018\184-\216\201\r\226\224\153\228\217\217y\023y\241\212\202\197\022T\128\201\\\165\253\230\003;\1855\203\014B\208\153\154U\019\007\1279\223M\142K\019\177\193K\239\150\167\194c/\198\222\011\176\172\229\191\242\031\006\023D\223\021\000\b\026\005\178^\241\185#\143\167To\207\227\017@\028\012\220\233\162\155\179\143\139!\229\228\229\142&\195\229\129\180\155\240\191\216\130~\176T\218\219\221.\206\157\021(\167G \140\031\130\1652x(^(\017\146<\178\024/.\194\139#tU*\155\027\133b\145\240E\"\132\219j\164\165@\192\181\240\2286\b\229\n\181B\222\226\015\004=\028\020c\0069x\016\216\131\000\231\004\153\224x\161X\192\238\141\252\170rK?\137}\168\029|\019\138\181\212D5\223_\200\011\183\141\255J\244oK\233S\1895i\188\150\200^\182@\\Dy\191@|o\249\005!\2130\159E\143@\230\025\140\012\138\192\204\215\194\142U\131\007a\005\157(@FQ\179\145z\251}\230\011\248\192\219G\225U\240-`y\203\129\154\224\239y\t\248\249\241\227\"\156\005\195\198\248\227\1772>\224\181\021!#c\207\137\186\209\021\005\2172D>de\181l\250\155\179\189\165Q\153\226\251v\031\239\143w&\252\248_\026N\1642\r#\027u\001\149\000!L,\149]\247O\201Q!\202\140W\231e\248\204\011\132\134\186r\201\002\222\164\144\215\197\157b\1784\133\247\253\1835\153j\004\"\183\212N\250af\225\031\155\138\128\163\199\148:\170\029P%Ta\234\196h\144\148E&^o\142\215y\237x\154\130M\255m,F\141\140\t\198R\\\215\200X\188YFc\1667XO\153Z\025-\224\199%\230\240,d\025\143\001\136\193J\160\219q\"\nS\188\138\r7\231\135\235\205\004\226\193\155\227>8n\2301\143\179Q\150\148W,\185\193\128\179\1444b\140c\204@u\245[\139U\209oX\006c3[7\168kh\186\029\230m\146\201gm7';]8h HY\161\144\228\254_U_\153\196\rK\025[\172.\231hxpy>\007Z7l\165LS\191\197\025\223w!\029\014\242)\000LUe\156\184\152\193XB\200S\152v\205Y\248\231\211\219:\001\1598;hp2\230\182\233\144+\217&\006\165|t\019\209c)O\161/)zIx" @@ -128,8 +130,6 @@ module Internal = struct let d_79c029f6f746a52f4a8bc8b6280c5c88 = "ment,t)])}}),ot({type:\"textord\",names:[\"\\\\@char\"],props:{numArgs:1,allowedInText:!0},handler:function(e,t){for(var r=e.parser,a=Ut(t[0],\"ordgroup\").body,i=\"\",o=0;o=1114111)throw new n(\"\\\\@char with invalid code point \"+i);return l<=65535?s=String.fromCharCode(l):(l-=65536,s=String.fromCharCode(55296+(l>>10),56320+(1023&l))),{type:\"textord\",mode:r.mode,text:s}}});var Qt=function(e,t){var r=ft(e.body,t.withColor(e.color),!1);return Ke.makeFragment(r)},er=function(e,t){var r=Nt(e.body,t.withColor(e.color)),n=new Tt.MathNode(\"mstyle\",r);return n.setAttribute(\"mathcolor\",e.color),n};ot({type:\"color\",names:[\"\\\\textcolor\"],props:{numArgs:2,allowedInText:!0,argTypes:[\"color\",\"original\"]},handler:function(e,t){var r=e.parser,n=Ut(t[0],\"color-token\").color,a=t[1];return{type:\"color\",mode:r.mode,color:n,body:ht(a)}},htmlBuilder:Qt,mathmlBuilder:er}),ot({type:\"color\",names:[\"\\\\color\"],props:{numArgs:1,allowedInText:!0,argTypes:[\"color\"]},handler:function(e,t){var r=e.parser,n=e.breakOnTokenText,a=Ut(t[0],\"color-token\").color;r.gullet.macros.set(\"\\\\current@color\",a);var i=r.parseExpression(!0,n);return{type:\"color\",mode:r.mode,color:a,body:i}},htmlBuilder:Qt,mathmlBuilder:er}),ot({type:\"cr\",names:[\"\\\\\\\\\"],props:{numArgs:0,numOptionalArgs:1,argTypes:[\"size\"],allowedInText:!0},handler:function(e,t,r){var n=e.parser,a=r[0],i=!n.settings.displayMode||!n.settings.useStrictBehavior(\"newLineInDisplayMode\",\"In LaTeX, \\\\\\\\ or \\\\newline does nothing in display mode\");return{type:\"cr\",mode:n.mode,newLine:i,size:a&&Ut(a,\"size\").value}},htmlBuilder:function(e,t){var r=Ke.makeSpan([\"mspace\"],[],t);return e.newLine&&(r.classes.push(\"newline\"),e.size&&(r.style.marginTop=V(F(e.size,t)))),r},mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mspace\");return e.newLine&&(r.setAttribute(\"linebreak\",\"newline\"),e.size&&r.setAttribute(\"height\",V(F(e.size,t)))),r}});var tr={\"\\\\global\":\"\\\\global\",\"\\\\long\":\"\\\\\\\\globallong\",\"\\\\\\\\globallong\":\"\\\\\\\\globallong\",\"\\\\def\":\"\\\\gdef\",\"\\\\gdef\":\"\\\\gdef\",\"\\\\edef\":\"\\\\xdef\",\"\\\\xdef\":\"\\\\xdef\",\"\\\\let\":\"\\\\\\\\globallet\",\"\\\\futurelet\":\"\\\\\\\\globalfuture\"},rr=function(e){var t=e.text;if(/^(?:[\\\\{}$&#^_]|EOF)$/.test(t))throw new n(\"Expected a control sequence\",e);return t},nr=function(e,t,r,n){var a=e.gullet.macros.get(r.text);null==a&&(r.noexpand=!0,a={tokens:[r],numArgs:0,unexpandable:!e.gullet.isExpandable(r.text)}),e.gullet.macros.set(t,a,n)};ot({type:\"internal\",names:[\"\\\\global\",\"\\\\long\",\"\\\\\\\\globallong\"],props:{numArgs:0,allowedInText:!0},handler:function(e){var t=e.parser,r=e.funcName;t.consumeSpaces();var a=t.fetch();if(tr[a.text])return\"\\\\global\"!==r&&\"\\\\\\\\globallong\"!==r||(a.text=tr[a.text]),Ut(t.parseFunction(),\"internal\");throw new n(\"Invalid token after macro prefix\",a)}}),ot({type:\"internal\",names:[\"\\\\def\",\"\\\\gdef\",\"\\\\edef\",\"\\\\xdef\"],props:{numArgs:0,allowedInText:!0,primitive:!0},handler:function(e){var t=e.parser,r=e.funcName,a=t.gullet.popToken(),i=a.text;if(/^(?:[\\\\{}$&#^_]|EOF)$/.test(i))throw new n(\"Expected a control sequence\",a);for(var o,s=0,l=[[]];\"{\"!==t.gullet.future().text;)if(\"#\"===(a=t.gullet.popToken()).text){if(\"{\"===t.gullet.future().text){o=t.gullet.future(),l[s].push(\"{\");break}if(a=t.gullet.popToken(),!/^[1-9]$/.test(a.text))throw new n('Invalid argument number \"'+a.text+'\"');if(parseInt(a.text)!==s+1)throw new n('Argument number \"'+a.text+'\" out of order');s++,l.push([])}else{if(\"EOF\"===a.text)throw new n(\"Expected a macro definition\");l[s].push(a.text)}var h=t.gullet.consumeArg().tokens;return o&&h.unshift(o),\"\\\\edef\"!==r&&\"\\\\xdef\"!==r||(h=t.gullet.expandTokens(h)).reverse(),t.gullet.macros.set(i,{tokens:h,numArgs:s,delimiters:l},r===tr[r]),{type:\"internal\",mode:t.mode}}}),ot({type:\"internal\",names:[\"\\\\let\",\"\\\\\\\\globallet\"],props:{numArgs:0,allowedInText:!0,primitive:!0},handler:function(e){var t=e.parser,r=e.funcName,n=rr(t.gullet.popToken());t.gullet.consumeSpaces();var a=function(e){var t=e.gullet.popToken();return\"=\"===t.text&&\" \"===(t=e.gullet.popToken()).text&" - let d_7a053e62260d74e8005f37b6c843a50e = "@charset \"UTF-8\";\n/* Copyright (c) 2016 The odoc contributors. All rights reserved.\n Distributed under the ISC license, see terms at the end of the file.\n %%NAME%% %%VERSION%% */\n\n/* Fonts */\n@import url('https://fonts.googleapis.com/css?family=Fira+Mono:400,500');\n@import url('https://fonts.googleapis.com/css?family=Noticia+Text:400,400i,700');\n@import url('https://fonts.googleapis.com/css?family=Fira+Sans:400,400i,500,500i,600,600i,700,700i');\n\n:root,\n.light:root {\n --main-background: #FFFFFF;\n\n --color: #333333;\n --link-color: #2C94BD;\n --anchor-hover: #555;\n --anchor-color: #d5d5d5;\n --xref-shadow: #cc6666;\n --header-shadow: #ddd;\n --by-name-version-color: #aaa;\n --by-name-nav-link-color: #222;\n --target-background: rgba(187, 239, 253, 0.3);\n --target-shadow: rgba(187, 239, 253, 0.8);\n --pre-border-color: #eee;\n --code-background: #f6f8fa;\n\n --li-code-background: #f6f8fa;\n --li-code-color: #0d2b3e;\n --toc-color: #1F2D3D;\n --toc-before-color: #777;\n --toc-background: #f6f8fa;\n --toc-list-border: #ccc;\n\n --spec-summary-border-color: #5c9cf5;\n --spec-summary-background: var(--code-background);\n --spec-summary-hover-background: #ebeff2;\n --spec-details-after-background: rgba(0, 4, 15, 0.05);\n --spec-details-after-shadow: rgba(204, 204, 204, 0.53);\n}\n\n.dark:root {\n --main-background: #202020;\n --code-background: #222;\n --line-numbers-background: rgba(0, 0, 0, 0.125);\n --navbar-background: #202020;\n\n --color: #bebebe;\n --dirname-color: #666;\n --underline-color: #444;\n --visited-color: #002800;\n --visited-number-color: #252;\n --unvisited-color: #380000;\n --unvisited-number-color: #622;\n --somevisited-color: #303000;\n --highlight-color: #303e3f;\n --line-number-color: rgba(230, 230, 230, 0.3);\n --unvisited-margin-color: #622;\n --border: #333;\n --navbar-border: #333;\n --code-color: #ccc;\n\n --li-code-background: #373737;\n --li-code-color: #999;\n --toc-color: #777;\n --toc-background: #252525;\n\n --hljs-link: #999;\n --hljs-keyword: #cda869;\n --hljs-regexp: #f9ee98;\n --hljs-title: #dcdcaa;\n --hljs-type: #ac885b;\n --hljs-meta: #82aaff;\n --hljs-variable: #cf6a4c;\n}\n\n@media (prefers-color-scheme: dark) {\n :root {\n --main-background: #202020;\n --code-background: #333;\n --line-numbers-background: rgba(0, 0, 0, 0.125);\n --navbar-background: #202020;\n\n --meter-unvisited-color: #622;\n --meter-visited-color: #252;\n --meter-separator-color: black;\n\n --color: #bebebe;\n --dirname-color: #666;\n --underline-color: #444;\n --visited-color: #002800;\n --visited-number-color: #252;\n --unvisited-color: #380000;\n --unvisited-number-color: #622;\n --somevisited-color: #303000;\n --highlight-color: #303e3f;\n --line-number-color: rgba(230, 230, 230, 0.3);\n --unvisited-margin-color: #622;\n --border: #333;\n --navbar-border: #333;\n --code-color: #ccc;\n --by-name-nav-link-color: var(--color);\n\n --li-code-background: #373737;\n --li-code-color: #999;\n --toc-color: #777;\n --toc-before-color: #777;\n --toc-background: #252525;\n --toc-list-border: #ccc;\n --spec-summary-hover-background: #ebeff2;\n --spec-details-after-background: rgba(0, 4, 15, 0.05);\n --spec-details-after-shadow: rgba(204, 204, 204, 0.53);\n\n --hljs-link: #999;\n --hljs-keyword: #cda869;\n --hljs-regexp: #f9ee98;\n --hljs-title: #dcdcaa;\n --hljs-type: #ac885b;\n --hljs-meta: #82aaff;\n --hljs-variable: #cf6a4c;\n }\n}\n\n/* Reset a few things. */\n\nhtml, body, div, span, applet, object, iframe, h1, h2, h3, h4, h5, h6, p, blockquote, pre, a, abbr, acronym, address, big, cite, code, del, dfn, em, img, ins, kbd, q, s, samp, small, strike, strong, sub, sup, tt, var, b, u, i, center, dl, dt, dd, ol, ul, li, fieldset, form, label, legend, table, caption, tbody, tfoot, thead, tr, th, td, article, aside, canvas, details, embed, figure, figcaption, footer, header, hgroup, menu, nav, output, ruby, section, summary, time, mark, audio, video {\n padding: 0;\n border: 0;\n font: inherit;\n vertical-align: baseline;\n\n}\n\ntable {\n border-collapse: collaps" - let d_7c9075f31df2a532c3135ae327c84a92 = "inline-block;left:calc(50% + .3em);position:absolute;text-align:right}.katex-display{display:block;margin:1em 0;text-align:center}.katex-display>.katex{display:block;text-align:center;white-space:nowrap}.katex-display>.katex>.katex-html{display:block;position:relative}.katex-display>.katex>.katex-html>.tag{position:absolute;right:0}.katex-display.leqno>.katex>.katex-html>.tag{left:0;right:auto}.katex-display.fleqn>.katex{padding-left:2em;text-align:left}body{counter-reset:katexEqnNo mmlEqnNo}\n" let d_7df05ceea77c14d78f1f1df8f98def4f = "deEnd, returnEnd not compatible with endScope: {}\"),\nG\n;if(\"object\"!=typeof e.endScope||null===e.endScope)throw K(\"endScope must be object\"),\nG;Z(e,e.end,{key:\"endScope\"}),e.end=E(e.end,{joinWith:\"\"})}})(e)}function V(e){\nfunction t(t,n){\nreturn RegExp(g(t),\"m\"+(e.case_insensitive?\"i\":\"\")+(e.unicodeRegex?\"u\":\"\")+(n?\"g\":\"\"))\n}class n{constructor(){\nthis.matchIndexes={},this.regexes=[],this.matchAt=1,this.position=0}\naddRule(e,t){\nt.position=this.position++,this.matchIndexes[this.matchAt]=t,this.regexes.push([t,e]),\nthis.matchAt+=b(e)+1}compile(){0===this.regexes.length&&(this.exec=()=>null)\n;const e=this.regexes.map((e=>e[1]));this.matcherRe=t(E(e,{joinWith:\"|\"\n}),!0),this.lastIndex=0}exec(e){this.matcherRe.lastIndex=this.lastIndex\n;const t=this.matcherRe.exec(e);if(!t)return null\n;const n=t.findIndex(((e,t)=>t>0&&void 0!==e)),i=this.matchIndexes[n]\n;return t.splice(0,n),Object.assign(t,i)}}class i{constructor(){\nthis.rules=[],this.multiRegexes=[],\nthis.count=0,this.lastIndex=0,this.regexIndex=0}getMatcher(e){\nif(this.multiRegexes[e])return this.multiRegexes[e];const t=new n\n;return this.rules.slice(e).forEach((([e,n])=>t.addRule(e,n))),\nt.compile(),this.multiRegexes[e]=t,t}resumingScanAtSamePosition(){\nreturn 0!==this.regexIndex}considerAll(){this.regexIndex=0}addRule(e,t){\nthis.rules.push([e,t]),\"begin\"===t.type&&this.count++}exec(e){\nconst t=this.getMatcher(this.regexIndex);t.lastIndex=this.lastIndex\n;let n=t.exec(e)\n;if(this.resumingScanAtSamePosition())if(n&&n.index===this.lastIndex);else{\nconst t=this.getMatcher(0);t.lastIndex=this.lastIndex+1,n=t.exec(e)}\nreturn n&&(this.regexIndex+=n.position+1,\nthis.regexIndex===this.count&&this.considerAll()),n}}\nif(e.compilerExtensions||(e.compilerExtensions=[]),\ne.contains&&e.contains.includes(\"self\"))throw Error(\"ERR: contains `self` is not supported at the top-level of a language. See documentation.\")\n;return e.classNameAliases=r(e.classNameAliases||{}),function n(s,o){const a=s\n;if(s.isCompiled)return a\n;[T,D,F,P].forEach((e=>e(s,o))),e.compilerExtensions.forEach((e=>e(s,o))),\ns.__beforeBegin=null,[L,B,H].forEach((e=>e(s,o))),s.isCompiled=!0;let c=null\n;return\"object\"==typeof s.keywords&&s.keywords.$pattern&&(s.keywords=Object.assign({},s.keywords),\nc=s.keywords.$pattern,\ndelete s.keywords.$pattern),c=c||/\\w+/,s.keywords&&(s.keywords=$(s.keywords,e.case_insensitive)),\na.keywordPatternRe=t(c,!0),\no&&(s.begin||(s.begin=/\\B|\\b/),a.beginRe=t(a.begin),s.end||s.endsWithParent||(s.end=/\\B|\\b/),\ns.end&&(a.endRe=t(a.end)),\na.terminatorEnd=g(a.end)||\"\",s.endsWithParent&&o.terminatorEnd&&(a.terminatorEnd+=(s.end?\"|\":\"\")+o.terminatorEnd)),\ns.illegal&&(a.illegalRe=t(s.illegal)),\ns.contains||(s.contains=[]),s.contains=[].concat(...s.contains.map((e=>(e=>(e.variants&&!e.cachedVariants&&(e.cachedVariants=e.variants.map((t=>r(e,{\nvariants:null},t)))),e.cachedVariants?e.cachedVariants:q(e)?r(e,{\nstarts:e.starts?r(e.starts):null\n}):Object.isFrozen(e)?r(e):e))(\"self\"===e?s:e)))),s.contains.forEach((e=>{n(e,a)\n})),s.starts&&n(s.starts,o),a.matcher=(e=>{const t=new i\n;return e.contains.forEach((e=>t.addRule(e.begin,{rule:e,type:\"begin\"\n}))),e.terminatorEnd&&t.addRule(e.terminatorEnd,{type:\"end\"\n}),e.illegal&&t.addRule(e.illegal,{type:\"illegal\"}),t})(a),a}(e)}function q(e){\nreturn!!e&&(e.endsWithParent||q(e.starts))}class J extends Error{\nconstructor(e,t){super(e),this.name=\"HTMLInjectionError\",this.html=t}}\nconst Y=i,Q=r,ee=Symbol(\"nomatch\");var te=(t=>{\nconst i=Object.create(null),r=Object.create(null),s=[];let o=!0\n;const a=\"Could not find the language '{}', did you forget to load/include a language module?\",c={\ndisableAutodetect:!0,name:\"Plain text\",contains:[]};let g={\nignoreUnescapedHTML:!1,throwUnescapedHTML:!1,noHighlightRe:/^(no-?highlight)$/i,\nlanguageDetectRe:/\\blang(?:uage)?-([\\w-]+)\\b/i,classPrefix:\"hljs-\",\ncssSelector:\"pre code\",languages:null,__emitter:l};function b(e){\nreturn g.noHighlightRe.test(e)}function m(e,t,n){let i=\"\",r=\"\"\n;\"object\"==typeof t?(i=e,\nn=t.ignoreIllegals,r=t.language):(X(\"10.7.0\",\"highlight(lang, code, ...args) has been deprecated.\"),\nX(\"10.7.0\",\"Please use h" @@ -248,13 +248,15 @@ module Internal = struct let d_d1d8d575696cbb5a4994efc9e2862948 = "\\u23ab\",m=\"\\u23a9\",h=\"\\u23aa\",c=\"Size4-Regular\");var u=ar(o,c,a),p=u.height+u.depth,d=ar(h,c,a),f=d.height+d.depth,g=ar(m,c,a),v=g.height+g.depth,b=0,y=1;if(null!==s){var w=ar(s,c,a);b=w.height+w.depth,y=2}var k=p+v+b,S=k+Math.max(0,Math.ceil((t-k)/(y*f)))*y*f,M=n.fontMetrics().axisHeight;r&&(M*=n.sizeMultiplier);var z=S/2-M,A=[];if(A.push(lr(m,c,a)),A.push(mr),null===s){var T=S-p-v+.016;A.push(hr(h,T,n))}else{var B=(S-p-v-b)/2+.016;A.push(hr(h,B,n)),A.push(mr),A.push(lr(s,c,a)),A.push(mr),A.push(hr(h,B,n))}A.push(mr),A.push(lr(o,c,a));var C=n.havingBaseStyle(x.TEXT),q=Ke.makeVList({positionType:\"bottom\",positionData:z,children:A},C);return ir(Ke.makeSpan([\"delimsizing\",\"mult\"],[q],C),x.TEXT,n,i)},dr=.08,fr=function(e,t,r,n,a){var i=function(e,t,r){t*=1e3;var n=\"\";switch(e){case\"sqrtMain\":n=function(e,t){return\"M95,\"+(622+e+t)+\"\\nc-2.7,0,-7.17,-2.7,-13.5,-8c-5.8,-5.3,-9.5,-10,-9.5,-14\\nc0,-2,0.3,-3.3,1,-4c1.3,-2.7,23.83,-20.7,67.5,-54\\nc44.2,-33.3,65.8,-50.3,66.5,-51c1.3,-1.3,3,-2,5,-2c4.7,0,8.7,3.3,12,10\\ns173,378,173,378c0.7,0,35.3,-71,104,-213c68.7,-142,137.5,-285,206.5,-429\\nc69,-144,104.5,-217.7,106.5,-221\\nl\"+e/2.075+\" -\"+e+\"\\nc5.3,-9.3,12,-14,20,-14\\nH400000v\"+(40+e)+\"H845.2724\\ns-225.272,467,-225.272,467s-235,486,-235,486c-2.7,4.7,-9,7,-19,7\\nc-6,0,-10,-1,-12,-3s-194,-422,-194,-422s-65,47,-65,47z\\nM\"+(834+e)+\" \"+t+\"h400000v\"+(40+e)+\"h-400000z\"}(t,M);break;case\"sqrtSize1\":n=function(e,t){return\"M263,\"+(601+e+t)+\"c0.7,0,18,39.7,52,119\\nc34,79.3,68.167,158.7,102.5,238c34.3,79.3,51.8,119.3,52.5,120\\nc340,-704.7,510.7,-1060.3,512,-1067\\nl\"+e/2.084+\" -\"+e+\"\\nc4.7,-7.3,11,-11,19,-11\\nH40000v\"+(40+e)+\"H1012.3\\ns-271.3,567,-271.3,567c-38.7,80.7,-84,175,-136,283c-52,108,-89.167,185.3,-111.5,232\\nc-22.3,46.7,-33.8,70.3,-34.5,71c-4.7,4.7,-12.3,7,-23,7s-12,-1,-12,-1\\ns-109,-253,-109,-253c-72.7,-168,-109.3,-252,-110,-252c-10.7,8,-22,16.7,-34,26\\nc-22,17.3,-33.3,26,-34,26s-26,-26,-26,-26s76,-59,76,-59s76,-60,76,-60z\\nM\"+(1001+e)+\" \"+t+\"h400000v\"+(40+e)+\"h-400000z\"}(t,M);break;case\"sqrtSize2\":n=function(e,t){return\"M983 \"+(10+e+t)+\"\\nl\"+e/3.13+\" -\"+e+\"\\nc4,-6.7,10,-10,18,-10 H400000v\"+(40+e)+\"\\nH1013.1s-83.4,268,-264.1,840c-180.7,572,-277,876.3,-289,913c-4.7,4.7,-12.7,7,-24,7\\ns-12,0,-12,0c-1.3,-3.3,-3.7,-11.7,-7,-25c-35.3,-125.3,-106.7,-373.3,-214,-744\\nc-10,12,-21,25,-33,39s-32,39,-32,39c-6,-5.3,-15,-14,-27,-26s25,-30,25,-30\\nc26.7,-32.7,52,-63,76,-91s52,-60,52,-60s208,722,208,722\\nc56,-175.3,126.3,-397.3,211,-666c84.7,-268.7,153.8,-488.2,207.5,-658.5\\nc53.7,-170.3,84.5,-266.8,92.5,-289.5z\\nM\"+(1001+e)+\" \"+t+\"h400000v\"+(40+e)+\"h-400000z\"}(t,M);break;case\"sqrtSize3\":n=function(e,t){return\"M424,\"+(2398+e+t)+\"\\nc-1.3,-0.7,-38.5,-172,-111.5,-514c-73,-342,-109.8,-513.3,-110.5,-514\\nc0,-2,-10.7,14.3,-32,49c-4.7,7.3,-9.8,15.7,-15.5,25c-5.7,9.3,-9.8,16,-12.5,20\\ns-5,7,-5,7c-4,-3.3,-8.3,-7.7,-13,-13s-13,-13,-13,-13s76,-122,76,-122s77,-121,77,-121\\ns209,968,209,968c0,-2,84.7,-361.7,254,-1079c169.3,-717.3,254.7,-1077.7,256,-1081\\nl\"+e/4.223+\" -\"+e+\"c4,-6.7,10,-10,18,-10 H400000\\nv\"+(40+e)+\"H1014.6\\ns-87.3,378.7,-272.6,1166c-185.3,787.3,-279.3,1182.3,-282,1185\\nc-2,6,-10,9,-24,9\\nc-8,0,-12,-0.7,-12,-2z M\"+(1001+e)+\" \"+t+\"\\nh400000v\"+(40+e)+\"h-400000z\"}(t,M);break;case\"sqrtSize4\":n=function(e,t){return\"M473,\"+(2713+e+t)+\"\\nc339.3,-1799.3,509.3,-2700,510,-2702 l\"+e/5.298+\" -\"+e+\"\\nc3.3,-7.3,9.3,-11,18,-11 H400000v\"+(40+e)+\"H1017.7\\ns-90.5,478,-276.2,1466c-185.7,988,-279.5,1483,-281.5,1485c-2,6,-10,9,-24,9\\nc-8,0,-12,-0.7,-12,-2c0,-1.3,-5.3,-32,-16,-92c-50.7,-293.3,-119.7,-693.3,-207,-1200\\nc0,-1.3,-5.3,8.7,-16,30c-10.7,21.3,-21.3,42.7,-32,64s-16,33,-16,33s-26,-26,-26,-26\\ns76,-153,76,-153s77,-151,77,-151c0.7,0.7,35.7,202,105,604c67.3,400.7,102,602.7,104,\\n606zM\"+(1001+e)+\" \"+t+\"h400000v\"+(40+e)+\"H1017.7z\"}(t,M);break;case\"sqrtTall\":n=function(e,t,r){return\"M702 \"+(e+t)+\"H400000\"+(40+e)+\"\\nH742v\"+(r-54-t-e)+\"l-4 4-4 4c-.667.7 -2 1.5-4 2.5s-4.167 1.833-6.5 2.5-5.5 1-9.5 1\\nh-12l-28-84c-16.667-52-96.667 -294.333-240-727l-212 -643 -85 170\\nc-4-3.333-8.333-7.667-13 -13l-13-13l77-155 77-156c66 199.333 139 419.667\\n219 661 l218 661zM702 \"+t+\"H4000" + let d_d2d82183505374fa41992d8d4c34d47e = " > code {\n color: var(--link-color);\n}\n\n.odoc code {\n white-space: pre-wrap;\n}\n\n/* Code blocks (e.g. Examples) */\n\n.odoc pre code {\n font-size: 0.893rem;\n}\n\n/* Code lexemes */\n\n.keyword {\n font-weight: 500;\n}\n\n.arrow { white-space: nowrap }\n\n/* Module member specification */\n\n.spec {\n background-color: var(--spec-summary-background);\n border-radius: 3px;\n border-left: 4px solid var(--spec-summary-border-color);\n border-right: 5px solid transparent;\n padding: 0.35em 0.5em;\n}\n\nli:not(:last-child) > .def-doc {\n margin-bottom: 15px;\n}\n\n/* Spacing between items */\ndiv.odoc-spec,.odoc-include {\n margin-bottom: 2em;\n}\n\n.spec.type .variant p, .spec.type .record p {\n margin: 5px;\n}\n\n.spec.type .variant, .spec.type .record {\n margin-left: 2ch;\n list-style: none;\n display: flex;\n flex-wrap: wrap;\n row-gap: 4px;\n}\n\n.spec.type .record > code, .spec.type .variant > code {\n min-width: 40%;\n}\n\n.spec.type > ol {\n margin-top: 0;\n margin-bottom: 0;\n}\n\n.spec.type .record > .def-doc, .spec.type .variant > .def-doc {\n min-width:50%;\n padding: 0.25em 0.5em;\n margin-left: 10%;\n border-radius: 3px;\n flex-grow:1;\n background: var(--main-background);\n box-shadow: 2px 2px 4px lightgrey;\n}\n\ndiv.def {\n margin-top: 0;\n text-indent: -2ex;\n padding-left: 2ex;\n}\n\ndiv.def-doc>*:first-child {\n margin-top: 0;\n}\n\n/* Collapsible inlined include and module */\n\n.odoc-include details {\n position: relative;\n}\n\n.odoc-include.shadowed-include {\n display: none;\n}\n\n.odoc-include details:after {\n z-index: -100;\n display: block;\n content: \" \";\n position: absolute;\n border-radius: 0 1ex 1ex 0;\n right: -20px;\n top: 1px;\n bottom: 1px;\n width: 15px;\n background: var(--spec-details-after-background, rgba(0, 4, 15, 0.05));\n box-shadow: 0 0px 0 1px var(--spec-details-after-shadow, rgba(204, 204, 204, 0.53));\n}\n\n.odoc-include summary {\n position: relative;\n margin-bottom: 1em;\n cursor: pointer;\n outline: none;\n}\n\n.odoc-include summary:hover {\n background-color: var(--spec-summary-hover-background);\n}\n\n/* FIXME: Does not work in Firefox. */\n.odoc-include summary::-webkit-details-marker {\n color: #888;\n transform: scaleX(-1);\n position: absolute;\n top: calc(50% - 5px);\n height: 11px;\n right: -29px;\n}\n\n/* Records and variants FIXME */\n\ndiv.def table {\n text-indent: 0em;\n padding: 0;\n margin-left: -2ex;\n}\n\ntd.def {\n padding-left: 2ex;\n}\n\ntd.def-doc *:first-child {\n margin-top: 0em;\n}\n\n/* Lists of @tags */\n\n.at-tags { list-style-type: none; margin-left: -3ex; }\n.at-tags li { padding-left: 3ex; text-indent: -3ex; }\n.at-tags .at-tag { text-transform: capitalize }\n\n/* Lists of modules */\n\n.modules { list-style-type: none; margin-left: -3ex; }\n.modules li { padding-left: 3ex; text-indent: -3ex; margin-top: 5px }\n.modules .synopsis { padding-left: 1ch; }\n\n/* Odig package index */\n\n.packages { list-style-type: none; margin-left: -3ex; }\n.packages li { padding-left: 3ex; text-indent: -3ex }\n.packages li a.anchor { padding-right: 0.5ch; padding-left: 3ch; }\n.packages .version { font-size: 10px; color: var(--by-name-version-color); }\n.packages .synopsis { padding-left: 1ch }\n\n.by-name nav a {\n text-transform: uppercase;\n font-size: 18px;\n margin-right: 1ex;\n color: var(--by-name-nav-link-color,);\n display: inline-block;\n}\n\n.by-tag nav a {\n margin-right: 1ex;\n color: var(--by-name-nav-link-color);\n display: inline-block;\n}\n\n.by-tag ol { list-style-type: none; }\n.by-tag ol.tags li { margin-left: 1ch; display: inline-block }\n.by-tag td:first-child { text-transform: uppercase; }\n\n/* Odig package page */\n\n.package nav {\n display: inline;\n font-size: 14px;\n font-weight: normal;\n}\n\n.package .version {\n font-size: 14px;\n}\n\n.package.info {\n margin: 0;\n}\n\n.package.info td:first-child {\n font-style: italic;\n padding-right: 2ex;\n}\n\n.package.info ul {\n list-style-type: none;\n display: inline;\n margin: 0;\n}\n\n.package.info li {\n display: inline-block;\n margin: 0;\n margin-right: 1ex;\n}\n\n#info-authors li, #info-maintainers li {\n display: block;\n}\n\n/* Sidebar and TOC */\n\n.odoc-toc:before {\n display: block;\n content: \"Contents" + let d_d7b447b6bfc36721f581470728505547 = "3525,0,.9015],79:[0,.7,.08078,0,.73787],80:[0,.7,.08078,0,1.01262],81:[0,.7,.03305,0,.88282],82:[0,.7,.06259,0,.85],83:[0,.7,.19189,0,.86767],84:[0,.7,.29087,0,.74697],85:[0,.7,.25815,0,.79996],86:[0,.7,.27523,0,.62204],87:[0,.7,.27523,0,.80532],88:[0,.7,.26006,0,.94445],89:[0,.7,.2939,0,.70961],90:[0,.7,.24037,0,.8212],160:[0,0,0,0,.25]},\"Size1-Regular\":{32:[0,0,0,0,.25],40:[.35001,.85,0,0,.45834],41:[.35001,.85,0,0,.45834],47:[.35001,.85,0,0,.57778],91:[.35001,.85,0,0,.41667],92:[.35001,.85,0,0,.57778],93:[.35001,.85,0,0,.41667],123:[.35001,.85,0,0,.58334],125:[.35001,.85,0,0,.58334],160:[0,0,0,0,.25],710:[0,.72222,0,0,.55556],732:[0,.72222,0,0,.55556],770:[0,.72222,0,0,.55556],771:[0,.72222,0,0,.55556],8214:[-99e-5,.601,0,0,.77778],8593:[1e-5,.6,0,0,.66667],8595:[1e-5,.6,0,0,.66667],8657:[1e-5,.6,0,0,.77778],8659:[1e-5,.6,0,0,.77778],8719:[.25001,.75,0,0,.94445],8720:[.25001,.75,0,0,.94445],8721:[.25001,.75,0,0,1.05556],8730:[.35001,.85,0,0,1],8739:[-.00599,.606,0,0,.33333],8741:[-.00599,.606,0,0,.55556],8747:[.30612,.805,.19445,0,.47222],8748:[.306,.805,.19445,0,.47222],8749:[.306,.805,.19445,0,.47222],8750:[.30612,.805,.19445,0,.47222],8896:[.25001,.75,0,0,.83334],8897:[.25001,.75,0,0,.83334],8898:[.25001,.75,0,0,.83334],8899:[.25001,.75,0,0,.83334],8968:[.35001,.85,0,0,.47222],8969:[.35001,.85,0,0,.47222],8970:[.35001,.85,0,0,.47222],8971:[.35001,.85,0,0,.47222],9168:[-99e-5,.601,0,0,.66667],10216:[.35001,.85,0,0,.47222],10217:[.35001,.85,0,0,.47222],10752:[.25001,.75,0,0,1.11111],10753:[.25001,.75,0,0,1.11111],10754:[.25001,.75,0,0,1.11111],10756:[.25001,.75,0,0,.83334],10758:[.25001,.75,0,0,.83334]},\"Size2-Regular\":{32:[0,0,0,0,.25],40:[.65002,1.15,0,0,.59722],41:[.65002,1.15,0,0,.59722],47:[.65002,1.15,0,0,.81111],91:[.65002,1.15,0,0,.47222],92:[.65002,1.15,0,0,.81111],93:[.65002,1.15,0,0,.47222],123:[.65002,1.15,0,0,.66667],125:[.65002,1.15,0,0,.66667],160:[0,0,0,0,.25],710:[0,.75,0,0,1],732:[0,.75,0,0,1],770:[0,.75,0,0,1],771:[0,.75,0,0,1],8719:[.55001,1.05,0,0,1.27778],8720:[.55001,1.05,0,0,1.27778],8721:[.55001,1.05,0,0,1.44445],8730:[.65002,1.15,0,0,1],8747:[.86225,1.36,.44445,0,.55556],8748:[.862,1.36,.44445,0,.55556],8749:[.862,1.36,.44445,0,.55556],8750:[.86225,1.36,.44445,0,.55556],8896:[.55001,1.05,0,0,1.11111],8897:[.55001,1.05,0,0,1.11111],8898:[.55001,1.05,0,0,1.11111],8899:[.55001,1.05,0,0,1.11111],8968:[.65002,1.15,0,0,.52778],8969:[.65002,1.15,0,0,.52778],8970:[.65002,1.15,0,0,.52778],8971:[.65002,1.15,0,0,.52778],10216:[.65002,1.15,0,0,.61111],10217:[.65002,1.15,0,0,.61111],10752:[.55001,1.05,0,0,1.51112],10753:[.55001,1.05,0,0,1.51112],10754:[.55001,1.05,0,0,1.51112],10756:[.55001,1.05,0,0,1.11111],10758:[.55001,1.05,0,0,1.11111]},\"Size3-Regular\":{32:[0,0,0,0,.25],40:[.95003,1.45,0,0,.73611],41:[.95003,1.45,0,0,.73611],47:[.95003,1.45,0,0,1.04445],91:[.95003,1.45,0,0,.52778],92:[.95003,1.45,0,0,1.04445],93:[.95003,1.45,0,0,.52778],123:[.95003,1.45,0,0,.75],125:[.95003,1.45,0,0,.75],160:[0,0,0,0,.25],710:[0,.75,0,0,1.44445],732:[0,.75,0,0,1.44445],770:[0,.75,0,0,1.44445],771:[0,.75,0,0,1.44445],8730:[.95003,1.45,0,0,1],8968:[.95003,1.45,0,0,.58334],8969:[.95003,1.45,0,0,.58334],8970:[.95003,1.45,0,0,.58334],8971:[.95003,1.45,0,0,.58334],10216:[.95003,1.45,0,0,.75],10217:[.95003,1.45,0,0,.75]},\"Size4-Regular\":{32:[0,0,0,0,.25],40:[1.25003,1.75,0,0,.79167],41:[1.25003,1.75,0,0,.79167],47:[1.25003,1.75,0,0,1.27778],91:[1.25003,1.75,0,0,.58334],92:[1.25003,1.75,0,0,1.27778],93:[1.25003,1.75,0,0,.58334],123:[1.25003,1.75,0,0,.80556],125:[1.25003,1.75,0,0,.80556],160:[0,0,0,0,.25],710:[0,.825,0,0,1.8889],732:[0,.825,0,0,1.8889],770:[0,.825,0,0,1.8889],771:[0,.825,0,0,1.8889],8730:[1.25003,1.75,0,0,1],8968:[1.25003,1.75,0,0,.63889],8969:[1.25003,1.75,0,0,.63889],8970:[1.25003,1.75,0,0,.63889],8971:[1.25003,1.75,0,0,.63889],9115:[.64502,1.155,0,0,.875],9116:[1e-5,.6,0,0,.875],9117:[.64502,1.155,0,0,.875],9118:[.64502,1.155,0,0,.875],9119:[1e-5,.6,0,0,.875],9120:[.64502,1.155,0,0,.875],9121:[.64502,1.155,0,0,.66667],9122:[-99e-5,.601,0,0,.66667],9123:[.64502,1.155,0,0,.66667],9124:[.64502,1.155,0,0,.6666" let d_d896ed607935554480384cf03c5258c7 = "7I\160-\163\b\212\029\183\141\172\137\195\144\240L\159\015\189\144\017\165\230\2340\1670:Bn\006\239\211\146N\153\025-z\210e\137\178a\234`J\195#h\225\242\021P\154\159\029\145n)l/\161\244\003\160\165\138\r\189\202\\\027D`\146'>\168\239j\204\252\142\164\164\200R\142V\159\007\173!\246\165\244\201t\1628\023\1883\177\134\224\128U\234\230/\161a\025\183\143\213\"(\021\133\129\210J\137\196\184\174\181\156i\244\137Y\234%l\234\024\006\018\002w\186EH\151\003\167}\224\216+\206`$\171\026h\214\209\029J\241k\171q\208e5\005\017\203\244\1752y\022\235\230\006B\229\028\145\2080\027/\188\155\214\204\234ZT2cD\018\169Fu\162YWj)J:\170\171B\252\218\135N\153\233\183\252\027uJ\026\142\198\022\253\"g6\021.\029\155\254HW\248\191u\187:\017\132D\196$\164d\228H\020\026\131\197\225)(\169\168ih\233\232\025\153YX%\177If\151\"U\154t\0252e\021\219}\173\139[\182\028\185\242\228+P\168H\177\018\165<\178r\n\138J\202*\170j\234\026\154Z\218:\186z\250\006\134F\198&\166f\230\022\150\136\192\208N\155|l\183\t[M\218\239\029'\156L\161w]\015\n0\128C\031\248\208G\222\243I\004\128\000B \002b \001R \003r@\002\n:\229\180G\157\245\1363\217\b\150/\024p\188\248\241\194x\200\171\215\239\031\208\249\184\249\143B\135\149w\015\014v\219N\196\235\143on\198\250g/\235\198\171\187\007{\250\186\225\230\00182\128E\007\230\1805\142/Z:0\127\225\002$\210?\128Dv\173\027\255\241\212c\224z\249\162_\212\127\232\165\203\159\004\217\169\004\191G\190\217s\018\018\204\211v\b\150j\246?\163!\228(,:<\"\t\231`K8/\b\222\198$a\226\r\137\031\001ydZ>\134\016P\224\181\130\177m\127\194\243\191\249\128\250${\2479\130\157\011\n\220\154|r\2009O|\021`\132\199\247\238\189L\244\170\207\232\b\n\133e\169\231`>8\250\206\131\197\253a\0318\0208\000\000\000" - let d_da739bd79e1901a19d34fbf2d1a16298 = ",LineNode:Q}};return t=t.default}()}));\n" + let d_d9618a035fab5935293da68eab054b9d = "\";\n text-transform: uppercase;\n font-size: 1em;\n margin: 1.414em 0 0.5em;\n font-weight: 500;\n color: var(--toc-before-color);\n line-height: 1.2;\n}\n\n.odoc-toc {\n position: fixed;\n top: 0px;\n bottom: 0px;\n left: 0px;\n max-width: 30ex;\n min-width: 26ex;\n width: 20%;\n background: var(--toc-background);\n overflow: auto;\n color: var(--toc-color);\n padding-left: 2ex;\n padding-right: 2ex;\n}\n\n.odoc-toc ul li a {\n font-family: \"Fira Sans\", sans-serif;\n font-size: 0.95em;\n color: var(--color);\n font-weight: 400;\n line-height: 1.6em;\n display: block;\n}\n\n.odoc-toc ul li a:hover {\n box-shadow: none;\n text-decoration: underline;\n}\n\n/* First level titles */\n\n.odoc-toc>ul>li>a {\n font-weight: 500;\n}\n\n.odoc-toc li ul {\n margin: 0px;\n}\n\n.odoc-toc ul {\n list-style-type: none;\n}\n\n.odoc-toc ul li {\n margin: 0;\n}\n.odoc-toc>ul>li {\n margin-bottom: 0.3em;\n}\n\n.odoc-toc ul li li {\n border-left: 1px solid var(--toc-list-border);\n margin-left: 5px;\n padding-left: 12px;\n}\n\n/* Mobile adjustements. */\n\n@media only screen and (max-width: 110ex) {\n body {\n margin: 2em;\n }\n .odoc-toc {\n position: static;\n width: auto;\n min-width: unset;\n max-width: unset;\n border: none;\n padding: 0.2em 1em;\n border-radius: 5px;\n margin-bottom: 2em;\n }\n}\n\n/* Print adjustements. */\n\n@media print {\n body {\n color: black;\n background: white;\n }\n body nav:first-child {\n visibility: hidden;\n }\n}\n\n/* Source code. */\n\n.source_container {\n display: flex;\n}\n\n.source_line_column {\n padding-right: 0.5em;\n text-align: right;\n background: #eee8d5;\n}\n\n.source_line {\n padding: 0 1em;\n}\n\n.source_code {\n flex-grow: 1;\n background: #fdf6e3;\n padding: 0 0.3em;\n color: #657b83;\n}\n\n/* Source directories */\n\n.odoc-directory::before {\n content: \"\240\159\147\129\";\n margin: 0.3em;\n font-size: 1.3em;\n}\n\n.odoc-file::before {\n content: \"\240\159\147\132\";\n margin: 0.3em;\n font-size: 1.3em;\n}\n\n.odoc-folder-list {\n list-style: none;\n}\n\n/* Syntax highlighting (based on github-gist) */\n\n.hljs {\n display: block;\n background: var(--code-background);\n padding: 0.5em;\n color: var(--color);\n overflow-x: auto;\n}\n\n.hljs-comment,\n.hljs-meta {\n color: #969896;\n}\n\n.hljs-string,\n.hljs-variable,\n.hljs-template-variable,\n.hljs-strong,\n.hljs-emphasis,\n.hljs-quote {\n color: #df5000;\n}\n\n.hljs-keyword,\n.hljs-selector-tag {\n color: #a71d5d;\n}\n\n.hljs-type,\n.hljs-class .hljs-title {\n color: #458;\n font-weight: 500;\n}\n\n.hljs-literal,\n.hljs-symbol,\n.hljs-bullet,\n.hljs-attribute {\n color: #0086b3;\n}\n\n.hljs-section,\n.hljs-name {\n color: #63a35c;\n}\n\n.hljs-tag {\n color: #333333;\n}\n\n.hljs-attr,\n.hljs-selector-id,\n.hljs-selector-class,\n.hljs-selector-attr,\n.hljs-selector-pseudo {\n color: #795da3;\n}\n\n.hljs-addition {\n color: #55a532;\n background-color: #eaffea;\n}\n\n.hljs-deletion {\n color: #bd2c00;\n background-color: #ffecec;\n}\n\n.hljs-link {\n text-decoration: underline;\n}\n\n.VAL, .TYPE, .LET, .REC, .IN, .OPEN, .NONREC, .MODULE, .METHOD, .LETOP, .INHERIT, .INCLUDE, .FUNCTOR, .EXTERNAL, .CONSTRAINT, .ASSERT, .AND, .END, .CLASS, .STRUCT, .SIG {\n color: #859900;;\n}\n\n.WITH, .WHILE, .WHEN, .VIRTUAL, .TRY, .TO, .THEN, .PRIVATE, .OF, .NEW, .MUTABLE, .MATCH, .LAZY, .IF, .FUNCTION, .FUN, .FOR, .EXCEPTION, .ELSE, .TO, .DOWNTO, .DO, .DONE, .BEGIN, .AS {\n color: #cb4b16;\n}\n\n.TRUE, .FALSE {\n color: #b58900;\n}\n\n.failwith, .INT, .SEMISEMI, .LIDENT {\n color: #2aa198;\n}\n\n.STRING, .CHAR, .UIDENT {\n color: #b58900;\n}\n\n.DOCSTRING {\n color: #268bd2;\n}\n\n.COMMENT {\n color: #93a1a1;\n}\n\n/*---------------------------------------------------------------------------\n Copyright (c) 2016 The odoc contributors\n\n Permission to use, copy, modify, and/or distribute this software for any\n purpose with or without fee is hereby granted, provided that the above\n copyright notice and this permission notice appear in all copies.\n\n THE SOFTWARE IS PROVIDED \"AS IS\" AND THE AUTHOR DISCLAIMS ALL WARRANTIES\n WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF\n MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR\n ANY SPECIAL, DIRECT, IND" - let d_dace847a98825928714b2dd186cf0e2e = " 2ex;\n}\n\n.odoc-toc ul li a {\n font-family: \"Fira Sans\", sans-serif;\n font-size: 0.95em;\n color: var(--color);\n font-weight: 400;\n line-height: 1.6em;\n display: block;\n}\n\n.odoc-toc ul li a:hover {\n box-shadow: none;\n text-decoration: underline;\n}\n\n/* First level titles */\n\n.odoc-toc>ul>li>a {\n font-weight: 500;\n}\n\n.odoc-toc li ul {\n margin: 0px;\n}\n\n.odoc-toc ul {\n list-style-type: none;\n}\n\n.odoc-toc ul li {\n margin: 0;\n}\n.odoc-toc>ul>li {\n margin-bottom: 0.3em;\n}\n\n.odoc-toc ul li li {\n border-left: 1px solid var(--toc-list-border);\n margin-left: 5px;\n padding-left: 12px;\n}\n\n/* Mobile adjustements. */\n\n@media only screen and (max-width: 95ex) {\n body.odoc {\n margin: 2em;\n }\n .odoc-toc {\n position: static;\n width: auto;\n min-width: unset;\n max-width: unset;\n border: none;\n padding: 0.2em 1em;\n border-radius: 5px;\n margin-bottom: 2em;\n }\n}\n\n/* Print adjustements. */\n\n@media print {\n body {\n color: black;\n background: white;\n }\n body nav:first-child {\n visibility: hidden;\n }\n}\n\n/* Syntax highlighting (based on github-gist) */\n\n.hljs {\n display: block;\n background: var(--code-background);\n padding: 0.5em;\n color: var(--color);\n overflow-x: auto;\n}\n\n.hljs-comment,\n.hljs-meta {\n color: #969896;\n}\n\n.hljs-string,\n.hljs-variable,\n.hljs-template-variable,\n.hljs-strong,\n.hljs-emphasis,\n.hljs-quote {\n color: #df5000;\n}\n\n.hljs-keyword,\n.hljs-selector-tag {\n color: #a71d5d;\n}\n\n.hljs-type,\n.hljs-class .hljs-title {\n color: #458;\n font-weight: 500;\n}\n\n.hljs-literal,\n.hljs-symbol,\n.hljs-bullet,\n.hljs-attribute {\n color: #0086b3;\n}\n\n.hljs-section,\n.hljs-name {\n color: #63a35c;\n}\n\n.hljs-tag {\n color: #333333;\n}\n\n.hljs-attr,\n.hljs-selector-id,\n.hljs-selector-class,\n.hljs-selector-attr,\n.hljs-selector-pseudo {\n color: #795da3;\n}\n\n.hljs-addition {\n color: #55a532;\n background-color: #eaffea;\n}\n\n.hljs-deletion {\n color: #bd2c00;\n background-color: #ffecec;\n}\n\n.hljs-link {\n text-decoration: underline;\n}\n\n/*---------------------------------------------------------------------------\n Copyright (c) 2016 The odoc contributors\n\n Permission to use, copy, modify, and/or distribute this software for any\n purpose with or without fee is hereby granted, provided that the above\n copyright notice and this permission notice appear in all copies.\n\n THE SOFTWARE IS PROVIDED \"AS IS\" AND THE AUTHOR DISCLAIMS ALL WARRANTIES\n WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF\n MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR\n ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES\n WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN\n ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF\n OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.\n ---------------------------------------------------------------------------*/\n" + let d_da739bd79e1901a19d34fbf2d1a16298 = ",LineNode:Q}};return t=t.default}()}));\n" let d_dc29762de1ae6c28b3b3cc202f52ac6f = "=je(l,t.fontWeight,t.fontShape),p=[l,t.fontWeight,t.fontShape]);if(Ve(i,u,a).metrics)return Ge(i,u,a,t,o.concat(p));if(we.hasOwnProperty(i)&&\"Typewriter\"===u.substr(0,10)){for(var f=[],g=0;g\245\180\176\017\196\153\023\183\135^Fs\250qX3\159\164\139#\183o\156\025d\031\209u\240\168\174\006" + let d_e9036d3c4fc740175253e5c2fd820e23 = "IRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES\n WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN\n ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF\n OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.\n ---------------------------------------------------------------------------*/\n" + let d_ecbaa97b8be9573105676709e2dbc384 = "3\252C\149\147\203\185\\r\202\173\144:G\211n\211\195\161\151\006X\177\234L\234\146(\017\194\186D\0211(\230S\228\157\171{\167\211\235T\184\155\187\199>\128(\168\012\185\203KKS\189\248\242\004\248\197\236\142\201\014\180\"\015Y1\224.\189\142N\201\r@U\211D\208\205\005\129%\217\231\192\128\149\127\158\216\015p\016\014I\247\194\176\1403\221\210\167\238\180\212\012v\141\251(\178]1\1759\018\157\161D\141\191\250``\172\026\201_z\255\226\210!\160\229Re\167#\128\178\025By8=\230\230\1288\030\167\023\014\250n\156\232\249\b\172\156\024(\215\145Cd\131\146F\194\213Z\250\188\152[\175E\248u\220\207\by\216\152\150\238\169\242\\\240\210j\197m\213\158a\181}\031\236\168gZ\201\019Et\213x\198e\158\215\002]\160\196\154\249\184\244D\016\168\152\147\022\030 \180\245\127\145\151:7C%\215\222\019\245\254\221N\019\233\135NxJ\156A\019\248;\217f5T\141bi9wIH\197C\171Kt\001\238\197\002\235\232*\172\022Dt\185\204e\200\210\168\216\029\242\224Qe\0054\225y\197+119\188\199Z\255k\231\019\132\212\225\186;S\007Y\218m+\191\204\028JI\206_\012\161\130\250\168\230\151\195\135\253\000I\216\179!\1764'}\250I8\208\135]\242Fj\002\140\135\014\239\165\002\210\141\177'\147w1J\169\181\169`K:p\007s\245*b\168\185\141\176I\186\0152\011\251\r\171\144\236j\237$\139Z\222\129\241\206R\133\n;\180[\255\238\200)\195%\193\026\213\158<=\233\007\182n\153\214q\146\193\181-\001\167\206\"\146\214?J4G\214\2181\160E\171\155\213A\165\133\253\185F\175\254\177\b\180e\231\140\219f\172T\218\154\218>Y}~\239\212\155\171\174\172\223\015\017\004\0123\173\020\228\148\2409\227K5\203^]\163e\133\011&\222\245p\206q\171\211H@\168U\149\130\245\251a^\158\149\n\031}\171\1734\160n\255WH.\005\151\2119\\\007\201\235\018\209\238\232_H\131\144\19167\247\182\146\181\000\174\194\166_\158~y\209/\237\029\140\184/~\143\219\253Rv\156$\251\220\146\167uPU\228\136\179\209\239\2547o\1275s\173\195\189\246\r\217\218e;\2021\018\177\012\251\141v\214C\172\177\150\139o\244\245\031Y?\250(y\011\219D\167\140\184\197/_\017`x\185:\252\229c\199\219t\130q\161#d\187\241}Q\\\130\160\161\214\029u\151\201\158\023'\200\157\021\191\150\001\002G\214-\176\222\172F2J\223!\211\012\182\226@\160\173PqP\247\249B\157P\1346yZ\029\150\146\205\129\187MD\218\227?\231)\245\019bn\155\244x\220SRV\210_Y\180[\167<\222\215Kj\234\150\185\194\r\253u\246\2430C\\\153\201\247\1796\150*.\231\004\023\tI\163=\159\217\170r\234\2522\182\149\236@\169\004)H>Q\029\156SY\028\157 ?\187h\255\254\216\195\212\020L'u\215Y\194\136\006\211`\022\006\206h\162\144\139 6\b\190\0034t\227Q\132\"\t\226\168t\239}\189\167\001\166\"\181'\241\025*\128O\023\135C\190G\183\015\177\193\135\216G\234d\193\238\207\239\004b\175\020\228P\209;\185\1907\229\030\157|UZ\242\158_m\185\206=\b\149\183]H,+\196\143&\019_\255\199E\238Eh\023\191\019\166\012\237(/\138.\019\1484\244\145\148\028\019\236q\027{T\175m\253\202\233/\235\171\158\231\176_\236\151d.8\192\231\1988\149\222+w\n\188,'F\020Z\025\2268_\254a\131\141\235DP\193\172F\188\012\163P\224\bY\182d\163#\249\155[38\159}\225\163\232b{\227\175\222p\153\026^c\016\202\014/7\006N\232{\203\2026\203\018\127\022`MTLL\023\174_\154\200\023r\252K\230\149\139N\176\153\187;X\232\180'0\235&\147r\018\146\178\172K\239~\194f\175\237\180-}\238\130\003\012\209\133\018Q\195\219\140\230\024G\240\239\133\210\184`'\227\207\130\176\145+\015\209\012\186\t\026\255\179$]Z+\204H\199J[\217\151\227\233\230\242\158\130o_0\186\246\t\216L\190\178\136_qQi\155\167$\192n\148B\021`\249\223kE1\174\193\165\024F\024Dv\156\251T{\200\221\172\253\187%!\185=g\203\019\230=\028\016<\132~H,\221\004C$\213\204\157fQ\176\194x=DK\\\243\249y_\234\202\205r\179\1827\173\164\241_\137\178\196\028\204\253oz\"\156\006\147Cb\205\216\230\0126\246\254\151U\238\241\186266U\146_z\169?Bi\"\147\237\143\217\146\206?\248\221\1925\153)\169K\202\r\153\187K\172\190~\149\189\011o\139w\240\186\171y\172\b\130\127\183k\169\178\234G\144\208h\170l\157\170}o4\156\153\129b\200\146\137\246\236\024\159\1779<[\179\231\243\187\204\212T\230\129\242\150\255C\198\148\018K\204\128B\197~\163\"\1506H\221x\253\137\150\248W\164\150\218\140\028\141c\197\225\236\180\184\185\"\226\004B?\203\131\2095\020\250k\230\212Y8cq\229\135]\011\238v\215\219\024\179to![\216\189\161zl*l\205\184+\030&\196\228\002\154\"G\243\135d\222bX\011SZ\168@\223Pw\235\185\153\021uB\219\022b\218\226(\012\167\188\221\199\229\015\188\154o\127\023\024\191\002\018\163\160\140\180\173n\161\134?\180\253\209{\023\179|\017\158\011\236\220\224\186ES\159TP\145\176\164\225!\164I\175\1479\220\198*\171\141EE\231\239\167\018\251\246\1484\028\208p{\135\243#\252\212\020\233\197\190'G\015Oj\162{\203\135\030+\167R\0300\146\181\247\242\145\242\240\141\011\b\197\156A\213Z\014\189\t\237\253\144?\221\190\234\196t\1285$\242\153\137\236co\207\025\189C \131A\128m\181\212\137u\149\026u>\223\209\192\141\200H@\146d\237\212\023\231W\209\151\146\003hG|\247\170\007/\235\221\"\144\240a\254|na\216\2212\181hy\244\224c\178V\127\006\147m\157y\221\164\191d\230o\152 C\185#\001\217\004\007Y\227\135\011B\222&v|W\188\209\158\219I\146\002\028\233\n\r\\\016q\129\190\223\193u\002\178'=\146\205>[L\178\tN\1643\225t%\149\"\192){\242|wE,jr4!\238\207#G\022\166)\232\168;q\209a\189\133\156\156<\210\180EX\028TS?\251\176&\185\154\149\250D\245\1625\158\129\148I\217\228\147\b\030\200\230\029\029\172,m\t\165\215\133\223\028r\011\213\150MY\130\004\163T\178\022\193\210%ed\242;C\003\129\253/\206w\206m\182\167Tg\006\180\222\148%\b-\195'W\255\223\025\214H\012P\004\251_\207c\018\191\148\199\133#\2153gL\187\255A\130\241\2433O\\\206kj\020\016\234\145\163\226\245y\222\1466SYU\132\234\180]\219\n(\197\025(\146\180\1897\184t<\213\145\182}\144\151\150\206\003\021\177\135+\223Y\1350x\006. \247\226\168\167\145\203\143A\0191+\251\227\133n\131\227\006\005\030\242\165\011\156,.\005\141\220\142Uu\137\229R\222\194\245\171\230\132L\151\014\243\002N\190`H\233|\242\221\225TU\151\160\245\147E'p\137\198\127-+e6!\248\229h\143\182!a\161TB\130\128\168]\178Ni\137\157\175\228\165\127\146$\245\148N\152\195\225\176\254\019\143*\031i\130\031q\154\250\027\253m\016\140F\227f\149\240\007\231\180\b\189=\131bG\224\226j\127\127\1917f)\207s\165\139x\229\161\251_\128\1680\165W\201\023\156&_s4\150\245z\170:\167Q\217\214RY\226\241\135\151\152\140\007\217tf\028\245J\211\174\231a@\234\016\172\247\255\150\188J15\1817^\148\176\016g%\229W\180tTq\171\222\143\236& \132\210LE\242\220\251o#\016\129\016\026\142\226\031dle4\191c\195_\003n\012\222\132\136~\211D\012\155\224\025D\022U\191\224\188\210\241\215\188\142\211\219\179b\156\253\255\238\1397\2291*\\\214\234\253\164\016G\231\227\023\002\129?\1830\244\139\r\250\173\215?\200\131\207\246\168\000\131\017\223\204\156\164\022r_\203\164)r\022\1494\1730\237pqx`]`\016{\219\173\190\006\188\252\234\212k>\225\181NR\136c\029\1276y\160\030i\210\224h$y\205\182\175\029t\173\"\249P\021\"\165\165\213\253\211f0F\154\142\134\001\188\249\187\027\0297\251\167\174\187\222J\152Zt \141\166'\002g7\132\147]\185\007j\2440lA$\193\012\206{2WJj\231\183\127L\166\201\164_\132:=u\145\239>\183\023W\b9m4\221\181\023\152\242ek\229\254\178\005\223\162\154\023Th\016\207i9\207\175\181*V\1510\233\001\213\205tA\236\178\195\197\181\004]\213\029N\199\145y}![\254_\184\023\228\238\227\014,\151p?\0146\229\150\030\222\192\197D\209\2373\214\210h}\192\019\2187\255\248.\132:O\129\020z\138\252w\178\236\218X\209X\201\156\194j\021]N\147Y\011\175=%5\000+N%\"06\169\179\154\171j\248\246\176/\215\174/7\181\006n\\\191\249\189\187\242>\243^3\205\170\140\154\"\199>5W\230\002\168\151Y\237\252hn\249\028[\249\196;\r\207\127vX`n\232b\167\240$d3\201\159\018\224\127A\t\206\146\196\204\178d\151{\215\131\174^\167\179T\250\164\164B\129\198\163\176\030~0=\0162F\023\239\127\175\247\222v))%\243&\021\190\n\161\002s+\163\167N\207\030\248 {\249\193~\249.\001\163\165\028\028P\011S\246f\2417{\200\218\250)\127\175\242\164\141$\136\bzH\019\196\027^`\015\188w\\\142'V\0228\183=\137\139\r\241\142\230\233\129\206\218(k\146_\nWU\248\t\156\222Q\185x\252\212\137*K\234\237.\255\174\228\208\002\134O[\214\025\157_\177\191H=\174\229\156\237>\179\167\168\170rBX\186\134\006o\186\249\199\243\171I\0209\254.r7\190\195M\133QD\248\161\153\181\140^U\186\205\2244\2461Js\t\144\140\192\017\152\222\199o/\174\015\207\239\241(~_\202Q]\223\145\133\192\218\232\206y\b\245\2523\b\029&)R\001Y#3\240)(\251\248yl\222\225\130\249\205\199\219w\214\212\200{\178\221\161SY\222\030+3!)\1331\235Z\244\225N\163K\212\130s\t\2428LK E\241K\191S97\247\189\243#5G\153\157\208\150\2183V=\221s\136%0~\216O\191\210\242\196\183\b\197\156\133\135_#\129~A\145U\227fM\216\030\012\137x\2079\0035\021wb\245\157e\014\252/{R\192L\182r\226\214\198K\228\188\132\252\180\130\141^\183\173\229\127\194\241.sI\143\171D\206x0\170\128\155\150ul\130\232\135\130~\230r\\D\245.3y\234,\161\209\147\197\156\196\155\237|\164\2503\205+o?\157\1468\166\024\219\166\253>'\180riR\150\2154\188\218\029\204\nR\006\201\210\014\189\2295E\234\163\201\237\255{o\173\223f\211\001\240\187\143u\171\163\\\127\174\147\132\017\166\149\249q\208\158\251\178\139\203\242\214\200\004z\158\147g1\134\228\146\028\135\004\215ev\029_\240\254\246\201\210\193\029\141\139\185\0175?\207\159k\145\236\024O\n\015\026\189[\226/\232Xr6\255\238\127\196\169\174\195\153\143\003\248\203\173?\ra\183\168K\230\197\205\139\167\1395$\021[\155\149\168\014(&\142M\254\1671\214\229\200\253\1347\215\016u\184\004+\148\161\198\255e\249\2351\150\201&\152\179\228\210\186\140\218\157$\141\132T0\141D\019k\156\177\183\197v\171\139f\161\231\020e\243\133\236\138\138\138Hd\129\186A^9\230\148\191r\029\015\196\003\236\139+s\249JA\246Iz\169S~\204\228\230\201\251\226h\255,Q\219\171\186\146E\156\t\007`)\"e\141E\229\252\\\127I\180\133J\129\bXt\142\243\185q\206\226e\149Y+/|\198c\006IR\192\247_\156\144\144\173g\143\203\030\202\254\030\242\213\169\253w\197T)\0026\135\018\245e\144\127\217s$)qN\189R\233H\140\163#\018H\178\160\204\191$\166\005\016 X\182\130\164\211\025\156\145.A\255\144\251\239Vo'\224\204\197\236\202\208.\148\165L{a\\Q\155\\\001\243\028xw\141\158\000\024b\153\148_\215|S\192T?\252\160\147\185\241s\251\174;s\201Y<[MV\157\180\212\015\213y\187\228w\1768\163o\153\227\211\007\211\003[x\131\201s\014\028\140cYr\235\2196\221.\164w\240\239;\247j\029\n\167\209s\007\220\237S[\130\209\172\njV\025|\022a\165\250xY\2502a\133\1615\234'0^\244\254\185\133\236 \153\194\165\184Rw^1\165\172\196~\251\156\231W|\130\160\168\175\250\142\237xf4h\171zj~\128\241\1770?\180B9\216\200]\243SS\202\137\ni\219\170$w\175\173\249*\235\214Wp\168\153(v\164\b7\165d\222\245\176\1504r~\228\198\247\188\156\148\236\176\019Y\206S\233p\018\005\1515\202\127\206`\006C\148'\006\r\161\021\007\005\004\135\127%3\253>\127\131)\188C+\134\136K8\149J\025\225\015\218\242\173\005A\246l\156E*$H!Q\241\204L\159\252\136\210\234+)d&\211\237\026\183\225\018\189Z\229\206`S\225[y5\133\"\178p\244\145\181g\172\225\0255\181\t\229R\000\000p\246\190\151&\030)\170\252\243\019\022\192v\222H\189Sm\229\144\185\248\188\251\177\242b\015\003\211\168\137\199\142~\225\204\210\216\171\244?\202\155'+:\2136\238\1838\156\206\210\188\191B\197\205#\165b\012\165\240\168h\238\246F\251\174\165\252\n%\145\187\142\133\017[3.\188\213\230\171/\237\249[O\b(\200\188@\238G\130\198\219\180\202\141\224\137\027^\187\217g\bU,\\K\004W\162X\184\016\199F\238\1569\224hU9\143\237rx\172MU\031|\176\250\1328\002\163\239\215X\247\b\007X\182\175\249\194\184o\211\155\179\132{/\227\159?`\166f\011\142\205\1484\184=\023\t=\130\206\021f\004$\014\205<\205p}w\176acM\204U\218J\018\156 \142\190\168\241j\134\149\237Y\193\028G\229\130N\030\244\230\023\158\246\2401Q^C\166\251)\189\211\153~\147\nG`\212\n\164\211\218,gUv\233\011\193\239v\1917V?\016!\190#\00486\1598\127,\248\164\151\167\011\253F\129\023n\190\242ic\203e\000-\252kt\152\029m" let d_edc3c186d80de2039375bef179a67067 = "546\1985\005\225\149q\159\172\199\209\192\151Y\226\022\024\028f!D\174C\015\138E\139\165\234KT\127-Y\148\246q\030x_p{\000\172w\242\164iW\178\024}n\223\199\003\031\1468A/HRD\230\139\146\213cX}\158\157\175Y\224\221%\242\143\251\156\228\2390\226r\147\250\146\140\230\237\166\157\004\224\002\011UQq=\213\176\232\214\203S\002\228\184\163\210\232g\153%\234\163\025\200\024\192\208EV\234\129`\237\023-\145\168%\015\222\\\022\196\r\bM\214\220\142\182\242J\145P\218\230&m\027\"?\028\251*\195\206\011Qp\140\023\178a\156\193M9Y1\149\\\163\211Tn\215\169a\248\148J\190\017\139\138y\137\185\204\147gc8\135\150\244\245\139\164\192\225\012\140\205\153\020\246\203\179\000w\150d\007\251\218\244M\"\0266\251\185\196\018\175\143\\u\r}\017i\222\213\027\137\202H\211\208W\146\217\138\138nUs\127\206Pg'\161\225DR\168\199\2284bhF\175\216\160\178E\1631C\188\212\180Q\134\141Y\024\n\2132}\1475\215\180\"\165\020\223r\214j\136\242#\213\129O'\173\180DD\215\011\021\202\216,\012\144\137\230$\226X\214+iX\\\229\214\tC\196~\182\024\206\140\137\188\217\177\138\129$\194q{\221\153H\016\200\146\153]P\194\173uK\021\205\181\246\210\144\212\180DA(\2261\149\n\252\207zn\232\161\204'\220ODw\229`C-\030\166\217B\236z.\179\158\215\181\016}]V\019+\223N\157\168\246\140\232\243\182\243\177A\137\228\144]\253x\155 \169\148\162\220R\015\139\015\196W\180\t\181r0\246c\242c\027\219\242\165\161\"\181\190\222\173\180\184\221\243!\015\150\174+J\214\185,\138\139 W.\212|\r\1497\000\022\199\146.\217\000\223\004\002l\026;=\1650bE\245\011%\137\129m\136\216F,\136w\159P\247Bc\t\199Ki\214\201\168qs\221\131zv\245\138v\174w[\136\143&\005\017+m7\173\139E\206]\209}2G9S\179\147 T\183Ri_\026\141#\028p\023\250\197\219\252\b(\002Y\243\"\017l\019 \162\151\232\003\019F\255\014\192\224u2Gn\rI\243\224\n\239\162\185Aqt}\001W\153KI\185B\131\007\227\197\136!\210\158:\235\190\153\208\232\149\233{&\021H\199\197M<\226Z\023\220\224-\128\196\023\170\166\018\242n\016\172\181\026\217\166\146{K\020\238\025\128\023u\147\029F\158D&\205\023\024r\208zn\176\128I>#\187\2429\014\175\173\024\229\250\156\230\173\004\155\132{\157\233:\012E\1847\178\240\153\156,\020\146\237\234\177X\202\153P\243\136\028\241ZA\240\240\245\230\132\129\135\214\209N\215SFU\146\147yQ.\157|\142\251\191X\211#\222(b\bW\192+jR~\168\203a\173(\184\169\143\255\148&,\232\021::\234d\"0\031\0195\012\247i\218l\217\138hN\244V\149\129\198\237\134E\244jI\235\242PZ\162\0167\b\164%j^\162lZ<\230\199\204\019\031!\182\029\187\234F\243\006\128\213y\199\017\151\001\168W\233\147g\215\228\190\183/[\250,\159yk\190<\189\231A\023\193\225\146\212\220\214?\185I*+\n9\144|\249\227H&\2234u\252\254Z\179\241\217;\202\164w\241\026\215*\022\141\177Eo\252\163\n\154\178\219\185\0295\251K\229X\214\244\164\172\205\\^\177\234\210\031\250\197\172\027\2078\168\182r_\169\006S\004\214\166\245\2007K\155\158^\212R\127`;\170(\135\164\r\142\185\173M\163\234\133g\020\150\007\1860\139w\190\143i\011\007K\203:\r\233\001eK,W\236\249b\218\178\234~In\145P\156fD\019\243\018\191\217\214\214h\240\237\171\183,;Q\198\163`T\012\225\244\245{|\191\204z\180\186>7\222\249h\224\24798\199\017\238\228\254\180i\136\007\160\138v?X\156\132@|\204\252MF\236\250\248\166Z\141\190\233O\173\203\201=G\143\004\207\199g\170\194\187S\227\023\007\164S\214W\230n\249\130\208\189p:2\184 \188\158\187\135\027\030:9\169\218`\190\218=\181\132\199\142\157\b[\159=\235\142\011\006\137;\190c\196\025\148\191\233\195\206.\n\211\202\226}\215\020V\173l/\239c\240~\228\225\228\191\158Z\227p\187+\029\027\203\190\145\177\216,n\254PS-\213,\163\1771\022\239\191>\159\236\241t\217j\142\192\192%\2374\207\208#\200\157D\149O\018\139>\245\213\139g@@\188.\127\135V\202&?M\161V\137\145\250\243\236\207\r\229\249\233:&\229\020T\169\146`p\007\145\130\129\241\206\140D\204\207~\244<\139E8\001\162\161\137\204\234\213\136\225h\184\153]D\249\215q\140z/E\164\216\249\176\194N\163\245]\127\021\127\134d\155\189Q\231zP\147\144\186\180.m\222j\209pE\209\t\208Tq\212\164\241\168\174\208\189Z\015\165\206x0\132 \202&\244\2488\129\182aBA4\235\\\022\029\225K\027Pu53p\250\020\016?(^b\249\137x\244kk\179IV\176\204\253?d\255\135\145\142Ef\206\0154\135\168N\156\151\205\161\185\n\132i\215\1757\174o\159@R\162\030\168\247@V\157\016m5\151\172q\150\140\166;+\142\246%\153\t\tq\191D:\170\2086\234\030\027\000\224\251\247\214\133\163=\148Nf\205F\201\011K\139\016\025\145\227\129\234\137\031\229\187\146E\173\0121\171q\251T\207\172\218\216\000\020\251\161\194\214\149\210\153m\209\216>\0183\250\208\216\007F\196\242#\146\147\196>\238\245m\148\016\145\175J\189\211\217v\175\221\142\154\247\"\212\134X\001h(fG\217\245\029\227\027\217Q\132\227\214l\150\170\203\031\227\241bO\255\183\020RVqc\139\224\233S\024\212ZE\221\255sg\201^]\174\217u\202\230\142e\130.q\214H\212A\251\145\147\156<\165\195\225\192\135\201m\234\252\134\012\127,\1836v\166\143k\251\244\006\155,,\220*\136\019\191\n\162\193Ym\157y\025q\219\248\206\128j\145]\220\243Q\022\1543\007\030\158a(\190\219\173\211t=\128%\220m\164\031\224.\238\2034}\142\157=lw<\026\175\152\220\185\167\182#\1981Q\131=\237e\210\186g\222\224\214\022\187\199\153\145\245\1483\189\011^z\017\014\251\187\194\220\187W\175M\028\168]*^h\176\152!\245e\231\167'\031\248u\228\0248\006I\002\015\241\171\160\174\189-\168/x\238s]\181,\001\156!u\192xoq]s^\165\186&Q{\201\192*\248O\233mQ\174\132h\145\1838R\229\235\251\209\169\189C\021M\219\156\021\023I\220\194?\180\021\161p\245\015\154\255\180\2166\216\239O\251\244\207\235|[~\162\205;\194\220\243\132\139\219\164\2167\208\151JvD\191#U\246\255cV\250\245\237\186l/\018 \232r\135\171[4M\137\220\136\161\232\020\183\205\233\170\011\238;5\028R\255v~0'T^\240\2095\248\018\201k\138\180S\206n\220o6Co\232io\209\017\175\174\031\1337\030\236)\155g\203k\170\205\151\243.\155\171kP\156\207x0\188\182\196\197o\228\190A\185Y\157\223\172\173\011\024\230Bo#\162\238\222y\163\180hj1spF\216~\222\235Q\251\158h/,\132\140W\216\222\196\188\245?\211\177\206\191\227\239t4=\029oT\012['\167r\029\184O\210\180\170}Qp\150!\176\182'\204[\168O&z\218R9iaj\221\162\208\140\194\206\011\154\174\185\251\195\162&\177\252\219\135\152q\017o\180\151]\223\236\139q\187;d\029\003\243r\235tie\206\142\160\169\183L\023\241)\220NJ\158\253\201\212c\141\003\214fZ(\239\158\193Vl\152#\020\222N\206\1741\210\178\030Z\028\022\148l\253o\239\024\152\131!*\174\252\150\242\203\204\167Z#v\129\238\\\160\254\247\028\007u\234.p;\220\179Q}\142\157\b\166\214o\001W\134\133\249\225U\162\130\213\006\207\144T\245\207h\024\132\132\179\252\207\022\023#W\170\204\193\186\235}\025\163c\170,\143c\249\021\160d\n\140N&m\216\nA\225\215\249_=\028\005\245\180\190\205)\203\140\198P\222\167@\217\193\129n\203\003\201\252\213q\193\202\187y]\029\170\173\221F\153\177<$\156q\027\228\170\131\027\203\189\236r\213\197\030\230\252\029\163\131\1897\234*\175\019\007\219\130\169\219n\003\163\029\236\225\205\195\203C\195\197\129\187\006\154\201\163s\206\r\244Vl\234\137%\162\229\\\134C\178\169k\014lj\004\023\023\240\131#\006/\179\151\147\235Z\\\020\1654A\206\214\211\000}\2421\226\140[\149\023\206\001\132\004\131\194\254C\007a}\001E\227\007\192!h\250\012\162k\226$`\198Xa\001z\141hKn\212\167\158\210z\2268\192D\163\194!\004w\238\210\031\018\023\229\223!\187\011\217lDV\195QN\003\172\168\132\196\178\137W0\146\237\015P\158\0209\216U=\171\135\004M\183\0237y\247\207\030\219\024\240\226HF4\250\242\191\195\212\153\147R\143\216&\216\222\203\222q\1339K\196\234\1521'\158G\224\016\184\170\016\168\152yXq@~\208f3~\193\253\024\168\146C?\134K\183J\183\244cp\251\025\132\006\136\003m\020\210KW\164h\211\238\135\0021\255x9\163\007#M\200\177\127Sq\007\237e\129\247\142(>>N\231B\021\128?\186f\243[0VP\186\137x\2330j}\2068\2110X\218\0259\027=\007v,\133l\221;ld\177\244}\029\153-\016\005S(\029\029\237|\238\\y)d\239_[_E\196/\193\229\025\232\005\141w3\030\238\231>\156\000\t\209\132\159\225\1726\160\186\150\238n\150\"x\156r`\186\237\208\142\217m\001\237m@\217\t\224s\189M\206t\212\172\221\243\230\249\170\132J\0312\1679\242,\239\192\184_\180X77U\179\006\168f\192u\254\224\184}3\231Y\156\238\184+Q\245\227\027\135M!\226\200\012\006\007\154Lhr\252\159ZC\173\001 \155\r\161eI\136/\001\196\245\167,\223\244c\168\231\022\204\231d\162\"{\182.Y\220\249\249\147|\243W\166O\211\216\140\007\219\005\142\234Wv4{\251\147#\157\1800\130$\145DO\188\219V\145*\181\195\134!\139.+Co\146faqid\235\139m\141F\003L\239\030}\224\249\148\221\014\135\022I.\016\170\235\129\n\136\200\191\235G\142F\202\230dHd\2505\206\191\141\021\134\242\252\150\135WW\204m\134gRgZ\251p\200z\149\020!\031\202\183\148\137p\200\031T\212U\175YNX\2513\0242\239aa}\146\236\0241cd\2171+@U\213EqS\231\211\129\150]\135\003" @@ -302,8 +306,6 @@ module Internal = struct let d_f98d809cc67734e6443e7dc4e47e3c27 = "\139\138tG8$\029\150\184\190\192\218\015\196D\141\218\239\127'-\150\138\136\t\131\1476\024\016\215k \196b\007\245\027\180u\001\207\170MG\199x\131,/&=\254\255O\206\240\168\156\2418W\023\188\018\189\023/a0\205\140\197I\211\131Ys\246\183g\214f\198\241y!\170a~mW\253\188\227\223N\151\150\250\137x'\240\031\231[Z@\168\158(\169\027Rw\129\028\017s\153\200\133\251iZ\181@\181\016LM\221\179\193\171/\201\\\195\149\204\004\153\2304 \165\239\024\138[\222f\167\167\208\186\238\228\228\236\204\180\133%\136\015\192SS\015\181\201f\208}\144\158p\007\189\011\227\028\0173\145\142\191D\228j-\177\219\1625\154\026FY\240\172\134\022\135\200\016\129\024|3\127\222J\175\\\177\011\214w2\024C]\201E9\193\147\136>\244\193\162%\248?\004Z\162pF\154\214\140Kz@E\007\016\245X\253\026\018\001\143\180\232/I\136\247\149\160F\127!4\023\014\242|\b\019\rQ\245\249\012\224r\244\243\2418(\002\002\213\025\133n5vY\147\246\026\252\002\218\190\002\131\193\r\206O\178\147\198\134TC\173\014\195\019@S\131\031\200\196\230\245q(?\b\129=m\162\168\144\195\227\245y\030S\1997%6\175\248\147\129\134D\216_\143\144#\174F\027\241\141\251\214\142\147L\222\198\212\188\146\212\229\244\216\232\003=dK\143:(\141\228\031\157\172\159\0218y\1832\145*wtd\145\151\181\195\218E\254\234\234\166\242\200\199\169\194\236qE\021\183r&\027w\237N\014RRVP\171\251\228K\b\198;C\236\186\202\128\255\162\191a\141\148\209\011u*\2305\253\187\164\004\1829B)61\145?\028x\011\t\142Y\166^~\232\223s;\019P\181\245\t\229`u=\180@9;\138\007^\148\202\254\175\199\158#\176}\024k\250!GQK\162FP\231\230\233w\236\201\221\176\031\250\1738\240\246\235\181\205\191\023\156$\147';\228o\197\227\r\021=U\021\177\152\229qQU~SVo\214\2526O\130\160j?=;\183'\230\204\236\177ts\007Y\138\006\217\159\018\254K#\250\207\238\174B\020\127\231P\233\022\240\234\155\144\177\149\155\017rP\217x,\225\144\188\129\215\226p\234F\025JL\1764U\n>\205|\1677+\165\019Q\225~\203\193\0273Z\012\151\145\217\196\191\255\195\167\019g\241\201\000\002\151\252Fy\226\128\185\027\144\175}\201\157\140\191\153\236\134R\205\242\185\1942\007\028\169\128:\205L\138\b=\133\205|\133\187\142\139J\153\129\202`\196]\227\249\155D\1527\223\191E\187CX\218P\164\152#\174[2\212\200\191\170mx\250\218\161\187\189\170`\016\231\178\210 _1_=\228v\132\243J=\028\127Oa\162\164:p\154!\176\188\178\251\252w\017\225\225J\169<\182G#\239\023E\224p\168\159-\178N\1349\233<-\248\025\2122$\002F\254\007d\148-D\203\021\0049\017JF\163\208\170\213\250MB\127\136\200\029\223\245\234#\199\212u\226\026\178\231\000\135j$\017\212\146\132\191`b\157'\005E\230\169s\176!\t\141\2192TT\171\173\246\199\223\254\170\200\178-\197\171\237vz'\007\205\134K\bwb\018\251\169_\209\007dD)\163,\248x\017\2060%\141I\000\226\137E\139\134\187\132\0071O\137\193\250\0204\185\169\020;\198\229\022\212\031J\233\174\191\003\224\202#\149\143'v\163\220Br\0060\155\186\129X&\002\180\243\200g?B\0297\208\015\158v\255\196cm9\169\248\161?\217\245\187\246>&\031\016\150\016l\1831F\198\145d@ \238\005U\221\128\020\149\018\161 '\141G\012[k\206\005\143\216\237\206\017\182\207<\\\157\165\156\tdlQ\153\240n%\166\133\2312\193\143\208\178\255\142M\188\163\150\225\172\249F\160O[\137\247\185H\029GD\174\230\147$\200\011\150\193\253\253\015\254\247X\248\225\151?lX\1895R\005u^\155\145\2004\206\243\238\018\137C)6\028\184E\230\251tL\020\026\225d\195R1 1\021\166\250,\249|=\187\165S\211\130\020#nm7\027\189\201\170\239\174\171\213\237\196\203\187\231\133d\183\029~G\030\145\170\145K_\165\216\154%\134\205yL\161Z$Y\190\147\t\135F\t\166d\167\215\159[\012\179C\188i\150\209\167\248\202\159;\191\175\182\136\199\192\007?'+\201\148\023R\231f\239\238E5\139\177OX\181\237\245\213\018\"7\255\003\199\243\0120x\133\195\027\004'\183\145\149\149\151\244\193\229\136@\148\131\168\151h\150\130\213\207\219\235\186\026\227R\023>\195\023\170\171\1796\149\005s_\186\216y_>\155d\145a\159\r\n\253\241\183\247\201*\012f\245\14064\r\164\154k\227\019l\220\156\024\r\205,\2098\158\214\203\238PY_/\132\205Yf\191\190\184E\2163G\025\239\152\248\235\251\225k<\214\165\242\168\157\155\131\154\177g|V\193\183) \237\150u\195\218\006'+\017\161\154\192w<\210l\179\207\163\203S\237+\002%\170\199\199\145\246\161jv%\147h\203/\143\015<\194\165\135\1885N\007\0159\251\253\139\143\154\017\235\206\251\175\201\247g\208\155\150I\002%\016\1764A\029\223`/\165L\170A.\252\165\143\232\239\208\158W>\b\188\222R\229\173\232\237W\nX\162\014\190/\1588\203U'F?\209\234?\215\201\255#\211n\232\003\204\004\199_\177\164\134\141\212\166 d\243{\197\208\225\149Q\024\146,\211\156\184\172Y\177N\255\224\004\153\251\167E\255\185^v\007\253\178\190\187!.\214\227=[\215\015`\180\191\160=\004\003\002\135\226}_\193\148\166u\235uk/?\171UE\178\022.Bn)\244\183\r\242\155\138\204\172q\175\203\021X\000\191\245\012\000\167\175v\204Q\217\213\197\199\199\158\180\028\217\155?\211e\252\006\147\150K\238\175\028\198N\180+\174\176\016\229D\012\172~~\245\200TnD\027\005D\021Y\165/+\211\188\137\228y\127f3\176\173~.\142\163[o\218\149\203\228i\t\180\251aQ\012\234\199&d\026\154_\243q\141!\197\187\235d%\185\023l\153g\205\178\255\200\012{^k`\188w\154O\021m\186f\1562\237\018\205C\247z\030*t\127v\205J\188({a0u\b\236\167\204\2177m\209\249\150\206Jn\214J\"c\147Zr^\162\012\141\193k\019\242j~\001\135\191\239?\178\000\247\031\201\162\220\143\221u\219\1516\031\162\1407\140\242\155\138\002\2449\180\168\130\206\021\2346\2347\130\156\\z'\1358W\231v\017\229Dy\172%G\2501\197&\"\165\171e2\208\246tW%\156v\185\196\186\205\186u\176L(Z.H\006\022\139\230\149c9\202\237\031\142\247\163\212%\201]\t\203\176\139\136\018\017\026\197\199\255;\249/\006o&[\247\175\159\245\163\213\231w\200\215\202\235\018\026.\185r\141e\246Q\003\003\229\242w\252\2502\239L\022\198\195eQ\223\186i\140\142\230Z\241\247\232\229\173\220P\190\243@?\026\145K\227\232wC\209\144\217\031\209'\175z1\2124\014\150\205m\229\235]:\195h\150z\189\184#\254\192\1841\231\196F\tk\022\189jy\196?><=\157X\207\148\165\162NW0\207$\250\218\208\188f\031\250\255\161hH\187/\227\251\217\226\186R\129i\199\143\203\230\182\b\180F\003\191\1827\170^\239\248r \255\rS\175\254\232\007\1989?\n\n9D\204\185\230\168!\195U?\240\142$L\250\006\nHkC5>\205+s\245e\224\239m;\152i\174\168\182~\169\005\156by\222\219\210\156+\023G9\168\024\200p\161\154\217F\151-X\128\149\004i\241\028\173\006\023\203\018\rY\007\245\131\162}\251\232\248\179\019\138\204\183\141\178\255\200\228\127\214\211\200R\156W+\248\200\236zS\229\020\166\t\153\210\205\127U\133\255\209P:\224K\221[t\168\184IR\149\205\207\188fj=I\158\226P\198\209v\221Q)Z\213T\026\144\229\0128&\208x\253\208og\219S\021\220i\1823\236\180\b\191\165W\148\195\024\028p\235\191){\014\196\204 \238\148\252!\230\167'\011\155{\234\255\251\023z\223\217.\214_1\200\238Hu\223\159TP\181\251\252\021\194\165\192\031\184\143\254\241\015\007\143r\251\187tumi`\020+\234\000\131\169\\\018\\}\222\011\229\133\153\152\135^\155\001Y\194v\223<5\024\244\"\175\022-\232\206\004D\178\133 ;\190\2494\022\\\003\216\tT3\230\146$\175\237\128Y\187\030\129\030\217\0161\168\014\233\199\170\188\160\244\205\210\235\160\178\189u\248\241\183\190\134\176^|\235\1615+5\024\167!\245\200\031\011\007\158\230J]'\174Hr&?u\244\181]\b\021\180V\141Jg+\255]\215\212\158\242\029\251\251\197\188\144v\r\030\202O\181\182$\235\162\185O\134\198d\221\162\202\199\030\133s\174[\203\214\137p\237\243\\\235\223\neZ\002\241\130\129~(\235\165\162Q\203cddX\160\229\136\240\024\144\007\1758\128$w\185\142\244\185\244\203\231\226\027\014Q\194\003\187\165\176\219\020\006\229\162\215S+0vO\250Xv\149\178e8\156s\b\236+\238\204\n\174|\011@ \176Cn\019\202\239\160?\199\006\017\140\169\191w\027z\027qo{\020\216\128\007\233f\179\184h\000$\2398\025\169u:MT\155\232\158A<;q\130^\243\145,\131`e\129\003\007\173tZgN\181\146)q\210Po\r\187\224\188\215\171\031a\173\166u\164H\183@\202\204|\148t\015\029\251\154&\164Q\183j\155\000\192\144\243\223\208\189\179\131u\152\b\196\211\180\136\160\215p\152\238\011\006\227\176\199C\031\225\178E\141\130\234zN.%\178\024\143\155\192\016\199S\220\183\177z\168\222\222\254\168\139\184\138r\152\246\1397\252\138\024\252\227\156\238\228\134\196z\t\167\174\239\200\232\019K\006\161\199\190)\231|\242\170<0\127\173\136\160\207(\145\150\031\002\195\169\235\167\143p\177zp\165#<\231\196\184\177\255\169\244\017N'\017J\174~\129\205\144\221\130+d\228\227\232\141g\019|)\210L*f>\158\205\159\163\243\127\209\20813!<\151\161?\026\222A\250\156\006\014\155\236*\211\024\171\169\252\185\195{%\250\237\250\245\000.,\r\028\002B\215\127;1\249\030\023\205\186\027\246\178R\166a\171q'\216\146+h\020\199*r>\174/\218IS\1904\134\022K\186k" - let d_fa492d3f7e09f1bd310e80bf0f4de6b4 = "ec-summary-border-color);\n border-right: 5px solid transparent;\n padding: 0.35em 0.5em;\n}\n\nli:not(:last-child) > .def-doc {\n margin-bottom: 15px;\n}\n\n/* Spacing between items */\ndiv.odoc-spec,.odoc-include {\n margin-bottom: 2em;\n}\n\n.spec.type .variant p, .spec.type .record p {\n margin: 5px;\n}\n\n.spec.type .variant, .spec.type .record {\n margin-left: 2ch;\n list-style: none;\n display: flex;\n flex-wrap: wrap;\n row-gap: 4px;\n}\n\n.spec.type .record > code, .spec.type .variant > code {\n min-width: 40%;\n}\n\n.spec.type > ol {\n margin-top: 0;\n margin-bottom: 0;\n}\n\n.spec.type .record > .def-doc, .spec.type .variant > .def-doc {\n min-width:50%;\n padding: 0.25em 0.5em;\n margin-left: 10%;\n border-radius: 3px;\n flex-grow:1;\n background: var(--main-background);\n box-shadow: 2px 2px 4px lightgrey;\n}\n\ndiv.def {\n margin-top: 0;\n text-indent: -2ex;\n padding-left: 2ex;\n}\n\ndiv.def-doc>*:first-child {\n margin-top: 0;\n}\n\n/* Collapsible inlined include and module */\n\n.odoc-include details {\n position: relative;\n}\n\n.odoc-include.shadowed-include {\n display: none;\n}\n\n.odoc-include details:after {\n z-index: -100;\n display: block;\n content: \" \";\n position: absolute;\n border-radius: 0 1ex 1ex 0;\n right: -20px;\n top: 1px;\n bottom: 1px;\n width: 15px;\n background: var(--spec-details-after-background, rgba(0, 4, 15, 0.05));\n box-shadow: 0 0px 0 1px var(--spec-details-after-shadow, rgba(204, 204, 204, 0.53));\n}\n\n.odoc-include summary {\n position: relative;\n margin-bottom: 1em;\n cursor: pointer;\n outline: none;\n}\n\n.odoc-include summary:hover {\n background-color: var(--spec-summary-hover-background);\n}\n\n/* FIXME: Does not work in Firefox. */\n.odoc-include summary::-webkit-details-marker {\n color: #888;\n transform: scaleX(-1);\n position: absolute;\n top: calc(50% - 5px);\n height: 11px;\n right: -29px;\n}\n\n/* Records and variants FIXME */\n\ndiv.def table {\n text-indent: 0em;\n padding: 0;\n margin-left: -2ex;\n}\n\ntd.def {\n padding-left: 2ex;\n}\n\ntd.def-doc *:first-child {\n margin-top: 0em;\n}\n\n/* Lists of @tags */\n\n.at-tags { list-style-type: none; margin-left: -3ex; }\n.at-tags li { padding-left: 3ex; text-indent: -3ex; }\n.at-tags .at-tag { text-transform: capitalize }\n\n/* Lists of modules */\n\n.modules { list-style-type: none; margin-left: -3ex; }\n.modules li { padding-left: 3ex; text-indent: -3ex; margin-top: 5px }\n.modules .synopsis { padding-left: 1ch; }\n\n/* Odig package index */\n\n.packages { list-style-type: none; margin-left: -3ex; }\n.packages li { padding-left: 3ex; text-indent: -3ex }\n.packages li a.anchor { padding-right: 0.5ch; padding-left: 3ch; }\n.packages .version { font-size: 10px; color: var(--by-name-version-color); }\n.packages .synopsis { padding-left: 1ch }\n\n.by-name nav a {\n text-transform: uppercase;\n font-size: 18px;\n margin-right: 1ex;\n color: var(--by-name-nav-link-color,);\n display: inline-block;\n}\n\n.by-tag nav a {\n margin-right: 1ex;\n color: var(--by-name-nav-link-color);\n display: inline-block;\n}\n\n.by-tag ol { list-style-type: none; }\n.by-tag ol.tags li { margin-left: 1ch; display: inline-block }\n.by-tag td:first-child { text-transform: uppercase; }\n\n/* Odig package page */\n\n.package nav {\n display: inline;\n font-size: 14px;\n font-weight: normal;\n}\n\n.package .version {\n font-size: 14px;\n}\n\n.package.info {\n margin: 0;\n}\n\n.package.info td:first-child {\n font-style: italic;\n padding-right: 2ex;\n}\n\n.package.info ul {\n list-style-type: none;\n display: inline;\n margin: 0;\n}\n\n.package.info li {\n display: inline-block;\n margin: 0;\n margin-right: 1ex;\n}\n\n#info-authors li, #info-maintainers li {\n display: block;\n}\n\n/* Sidebar and TOC */\n\n.odoc-toc:before {\n display: block;\n content: \"Contents\";\n text-transform: uppercase;\n font-size: 1em;\n margin: 1.414em 0 0.5em;\n font-weight: 500;\n color: var(--toc-before-color);\n line-height: 1.2;\n}\n\n.odoc-toc {\n position: fixed;\n top: 0px;\n bottom: 0px;\n left: 0px;\n max-width: 30ex;\n min-width: 26ex;\n width: 20%;\n background: var(--toc-background);\n overflow: auto;\n color: var(--toc-color);\n padding-left: 2ex;\n padding-right:" - let d_fadfd470a088dde5c3755136ac4b6188 = ".47534,0,0,.50181],53:[.18906,.47534,0,0,.50181],54:[0,.69141,0,0,.50181],55:[.18906,.47534,0,0,.50181],56:[0,.69141,0,0,.50181],57:[.18906,.47534,0,0,.50181],58:[0,.47534,0,0,.21606],59:[.12604,.47534,0,0,.21606],61:[-.13099,.36866,0,0,.75623],63:[0,.69141,0,0,.36245],65:[0,.69141,0,0,.7176],66:[0,.69141,0,0,.88397],67:[0,.69141,0,0,.61254],68:[0,.69141,0,0,.83158],69:[0,.69141,0,0,.66278],70:[.12604,.69141,0,0,.61119],71:[0,.69141,0,0,.78539],72:[.06302,.69141,0,0,.7203],73:[0,.69141,0,0,.55448],74:[.12604,.69141,0,0,.55231],75:[0,.69141,0,0,.66845],76:[0,.69141,0,0,.66602],77:[0,.69141,0,0,1.04953],78:[0,.69141,0,0,.83212],79:[0,.69141,0,0,.82699],80:[.18906,.69141,0,0,.82753],81:[.03781,.69141,0,0,.82699],82:[0,.69141,0,0,.82807],83:[0,.69141,0,0,.82861],84:[0,.69141,0,0,.66899],85:[0,.69141,0,0,.64576],86:[0,.69141,0,0,.83131],87:[0,.69141,0,0,1.04602],88:[0,.69141,0,0,.71922],89:[.18906,.69141,0,0,.83293],90:[.12604,.69141,0,0,.60201],91:[.24982,.74947,0,0,.27764],93:[.24982,.74947,0,0,.27764],94:[0,.69141,0,0,.49965],97:[0,.47534,0,0,.50046],98:[0,.69141,0,0,.51315],99:[0,.47534,0,0,.38946],100:[0,.62119,0,0,.49857],101:[0,.47534,0,0,.40053],102:[.18906,.69141,0,0,.32626],103:[.18906,.47534,0,0,.5037],104:[.18906,.69141,0,0,.52126],105:[0,.69141,0,0,.27899],106:[0,.69141,0,0,.28088],107:[0,.69141,0,0,.38946],108:[0,.69141,0,0,.27953],109:[0,.47534,0,0,.76676],110:[0,.47534,0,0,.52666],111:[0,.47534,0,0,.48885],112:[.18906,.52396,0,0,.50046],113:[.18906,.47534,0,0,.48912],114:[0,.47534,0,0,.38919],115:[0,.47534,0,0,.44266],116:[0,.62119,0,0,.33301],117:[0,.47534,0,0,.5172],118:[0,.52396,0,0,.5118],119:[0,.52396,0,0,.77351],120:[.18906,.47534,0,0,.38865],121:[.18906,.47534,0,0,.49884],122:[.18906,.47534,0,0,.39054],160:[0,0,0,0,.25],8216:[0,.69141,0,0,.21471],8217:[0,.69141,0,0,.21471],58112:[0,.62119,0,0,.49749],58113:[0,.62119,0,0,.4983],58114:[.18906,.69141,0,0,.33328],58115:[.18906,.69141,0,0,.32923],58116:[.18906,.47534,0,0,.50343],58117:[0,.69141,0,0,.33301],58118:[0,.62119,0,0,.33409],58119:[0,.47534,0,0,.50073]},\"Main-Bold\":{32:[0,0,0,0,.25],33:[0,.69444,0,0,.35],34:[0,.69444,0,0,.60278],35:[.19444,.69444,0,0,.95833],36:[.05556,.75,0,0,.575],37:[.05556,.75,0,0,.95833],38:[0,.69444,0,0,.89444],39:[0,.69444,0,0,.31944],40:[.25,.75,0,0,.44722],41:[.25,.75,0,0,.44722],42:[0,.75,0,0,.575],43:[.13333,.63333,0,0,.89444],44:[.19444,.15556,0,0,.31944],45:[0,.44444,0,0,.38333],46:[0,.15556,0,0,.31944],47:[.25,.75,0,0,.575],48:[0,.64444,0,0,.575],49:[0,.64444,0,0,.575],50:[0,.64444,0,0,.575],51:[0,.64444,0,0,.575],52:[0,.64444,0,0,.575],53:[0,.64444,0,0,.575],54:[0,.64444,0,0,.575],55:[0,.64444,0,0,.575],56:[0,.64444,0,0,.575],57:[0,.64444,0,0,.575],58:[0,.44444,0,0,.31944],59:[.19444,.44444,0,0,.31944],60:[.08556,.58556,0,0,.89444],61:[-.10889,.39111,0,0,.89444],62:[.08556,.58556,0,0,.89444],63:[0,.69444,0,0,.54305],64:[0,.69444,0,0,.89444],65:[0,.68611,0,0,.86944],66:[0,.68611,0,0,.81805],67:[0,.68611,0,0,.83055],68:[0,.68611,0,0,.88194],69:[0,.68611,0,0,.75555],70:[0,.68611,0,0,.72361],71:[0,.68611,0,0,.90416],72:[0,.68611,0,0,.9],73:[0,.68611,0,0,.43611],74:[0,.68611,0,0,.59444],75:[0,.68611,0,0,.90138],76:[0,.68611,0,0,.69166],77:[0,.68611,0,0,1.09166],78:[0,.68611,0,0,.9],79:[0,.68611,0,0,.86388],80:[0,.68611,0,0,.78611],81:[.19444,.68611,0,0,.86388],82:[0,.68611,0,0,.8625],83:[0,.68611,0,0,.63889],84:[0,.68611,0,0,.8],85:[0,.68611,0,0,.88472],86:[0,.68611,.01597,0,.86944],87:[0,.68611,.01597,0,1.18888],88:[0,.68611,0,0,.86944],89:[0,.68611,.02875,0,.86944],90:[0,.68611,0,0,.70277],91:[.25,.75,0,0,.31944],92:[.25,.75,0,0,.575],93:[.25,.75,0,0,.31944],94:[0,.69444,0,0,.575],95:[.31,.13444,.03194,0,.575],97:[0,.44444,0,0,.55902],98:[0,.69444,0,0,.63889],99:[0,.44444,0,0,.51111],100:[0,.69444,0,0,.63889],101:[0,.44444,0,0,.52708],102:[0,.69444,.10903,0,.35139],103:[.19444,.44444,.01597,0,.575],104:[0,.69444,0,0,.63889],105:[0,.69444,0,0,.31944],106:[.19444,.69444,0,0,.35139],107:[0,.69444,0,0,.60694],108:[0,.69444,0,0,.31944],109:[0,.44444,0,0,.95833],110:[0,.44444,0,0,.63889],111:[0,.44444,0,0,.575],112:[.19444,.44" let d_faf3026edac134ac18982c09dc18fcd1 = "\208{\012\221\212\233\181\132\197\021\208\211_\164\022|\168,\020\217jJ\218b\188\027j\026'&\234\014\218z\023;\195`\238R\251\186Q\231\165\150Dqj\188\219\153|\017\006\r\163^m\209\146\198\022\023!\151b\031\230Rv\029\253Z\148JK\000\140\204\188\163HM\219u\007\191\235\n{\180\181\005\254\153Q3!\129\230\177Z\144A\238=s`\191\160j\178\242#M\004\131\254\025\134B~\209\233\194\227\144\022<\026M\244H\146\251\b\n6\129\201$iy\158%\2425\241\223\164\232\n]\178t\025\209\194\130L*\159\1991C\138\bu|\165\169;\234\127\025\148w5\216\202\233a\224\018\164\152Dn\149e6\029\187E\156k\134\200w\011\002\130r\191r\136\253g\019gpj\166|\252\243\168o\147u>\171\228F{\158$M\134M`\020\162/Y2}~\140\169W:0\255Z?AZI \215\007Px=\137n\005\140LP\179@\218\205-L\226\238g?\167\135\196\169l\b6\129\209\184r\175\14460\183\166\208=$X\237\201\192\142\192\185%\161M\141`\018\216k\186C\243\237\147\147\132T8\182\160\130\222\188q\140\236\193l\137\174\015\006y\142\253b\171z`\210\248\215\191\231\166\150m\242\230\242\1887\165\150N\0159N1\186\025L>\"\162X\249\189\193\134bg\177e\156\224\226W\205`&\149Bj\189\239S\209\031@\019^\232\232\248D\0251GM\011\194\231Ao\003\141\019\141\134\197\128\011\226\223\137\167\026\203\219\003\218\203\027-\179\188\178\191\205\002n\218\139\145~\205U\1564\1313\149?+<%\156(OL\177\164\215s\029\242`]\145p\225*\162\228\214n\235N\155\218'&\218\171\245\182\183'2\245\213\243\174\232j\213\007\143?\021\243\238\015M,r\023\187/>\187'S\153\185\231\236b\229v\158\157\248\1808p\157}\189_\224I\223\192\014\132\133\144\214Eh84\251l\167B\017.\231\230\194f\244\144\132\129\135P\rT\193\177\171\251$F:;\145\195\030#w~o\206\011\149\252B\142\177]\166p\184Tr\230\216\177'oF\168G\232s\002M\246r5\230\"#8C\197\240\031\162\243\1659$B\186n\174$\193\201u&H\230\174U\031\229\176@\242\209\152T`\174\173\232^\167\\\195\223\019\007\248\r\030\\\015\139\007\233\225k\242\228zZo\190\186\157[\127\206\207\025\232|\181\235\165u\023V\162\171\127.~^\255U\2558\253\158\213\152RS\191\006\159\150\255p\168\146\134\175+OPba5\146X=\184~`4\247\t\197C%\249v\175\234Y\221\001:\2313\198\237\131\134\206\011\156\226\030\167)>\014\004\156c\255u\213\156\029m\216\001v=a1\166\154\230O\239\004[\018\143\159\023MO\014X\n\134p\236K\127\165\179\204Y\158\t\236\147\1847,+[?\205`\169jusa\129j\016\177\179\155\205X\250\031\248\255\232\234*j\002)\148t\163\193QV\128\237M\026^\186j\2010\024y\213d\127?'k\028\2314\129\206\174\1702U\rn\156\1837\1563\135[h\128YF0v\142\253\215\171\133\142\012Y\029\215\198\184\254q\155Ax?\128#xv\243\204\025v\247\220d\136z\171\247\022\231\151\131\242\201\185\1972\175[\136D\006\142\1875\142[P\157\024\236\171\198DZm(\187\201\023|\129\188}\005;\162\179\t\255\204!@\165\223x\163b\005\147\162\193\251?a3\012\164(R\193\192qG/D\252l\194\t\194T\130\227I\240\028\253\255p\\\224\193L%\168\140\004=\194\154=\157R\247\157\184\215n\142\022\220\159n\182Os\155\243\153>\234d\169`\154#y\216\r i\233\177\224\139\\z\026\002\214\021\171\244FM\192\153\000\129 `b\155M\016\1466\148\t\166\029\143\140X\127\005\2478\000p\1665\021|\026\187\219p\225\195\145\129q\166\251\231\022`\005\162[\180IN\195\139Y\191\233f\176(v[\170_\235\175\141\207\233\216\025\"\027\024\0225\189\148[f\191\181l\137\002\213\031\221\250\155\137\255\243\201\011\215\023 \2264cj\138D\227\030\189{}8\140\202H\"g\189m\253\157f\224\176\242\193\1953\015\n\146\024\2169\204\255\217'\002\243&\193f\130\012\159j\245\018\130\182Xj\002 \254\190n:\028\167\028vzz\171y^\222<5\253\154x\138]TdMK\164\1714sl\210\186\154\218\218\154\026\171\213\155\138\159\197(\153@\218PV>W\129\254\016;?nA\027q\132\203\019\011\152\171B#n\223\199\017\024\020\212\132\232_\157tW\209E<\238\145lVT\146\179\129\243\155\0128\222\217\014\207\148\2032Y/\254\179(\186\180\137\161\230\254c\015J\199\183\188`1_\142o-\235\250\007%\021=\127\149m\029\127\t\236t\163\129\1340.\170\223\224\149\204\201a\185E\212\236g\012ty\234\029\026\145\216\160H\253\239\185x\nM\023\017[\177\210\178\231 \135/n\252\216[\r\006\166A8\248m\222\\u\138\189/\006\217\163\163\222\185\017\026~\161$B^\226\230g_\215)\163\187\147\204\252\"\202\173\201\213lq\227\129\197l\235\182\127\003U\t\186\028\209\129\003\141\226\198\137%\204\212\206\134\206T\230\146\t\144\238d.\135\011\186\nUI\233\003\177\228H\026\2376\152\012)\159\251cp\199\141m\028\180:\031\244hZ/n:p@Tk\138,4\233j\133\007\193\254\152}\1807{\139@-\154\147\224\164\219\137m\137Q\141t\180Y\015\2092P\182\017g\205\191\132@@\161\232\145\171u\001\023\215\239J8w\164Q\220xx\133K\218\0233\166\153)\204_8_~a\174\169\n\2329T\237\006N\156\\\n\142si\2039\138E\203\019V\152*\025\204Y\177$\135\190\156\134\185\162\218\138\254\171\218z\222s\212\203gf\143\208kn\236(p\000\206R\026}\169\213\138\132\2291\187\147\012\207\245\249\214Mg\189\214\197\213x{\r\197\206\005\243}\1373\024\181\175\159\191\022.\227\249p|\228>\001\006\149\004}\196\193\1562\224\138\136\129\137Z\239b\tR\141\216\025\194\153\244\193\221\134\230\152\155\211\235#m\001\023\128\019\227<\194(n\195^\163\018\019\215\164\150\142\tVSB\219%(m\145ll\234\164\240\164\159\215\024\028\196\232g1\186S\224>j\227\173\170\210\202\156t\"\017\213_\131\162\213n#<-K\171\136\n\196\184|<\011\224K\241\165\187\243\132\171\029\129\164\131I\000\191\138Yr\201b\198\000\249\231\197i\243F\163\198\212G]\184\\\220\255\017\153\016\026\206+?\134}\228\221\202|\025\186\022!u\182\030\199oa*\229}\227\b\147Q)\011~\132\240HN\191\228\241\217\228\255\149z\208+\239d\128~@\213\148cgq\189\255\1950\206\170\240\127\132c\019\024\243\218\219\139\141\206\026\000E \2214[\tW\155\134?\157\189a\239\203>\005\024\2509$\151\018\252\tY\201`\142\000V5\191\014\216\207\2267\221\156\206\219\236\014\150\140?\159\162I{^\184Z\020-/\223\229+?N\000\199\207\240\188\226\019\153\015e\142\142.\029~\022#\003\024)\137uu\255\224n\147\229\245\167\221\002\199\002\241T\151\216\216\132\187\027\155\203y+=E\133;\145\233b\159\140\139\153\151I\011\219[x\146\164\030\193\149\249\193Pu\204P\023\"\205\222B\004r\241\253\024c\230\247\127D&6\203W\207\156\t\179\207\198H\215\188\223B|\211\170\253yL\232[\226[\156y\t:`*\194#B\191@\n!\136\004\228\\\161\244\011A\129u\006\229\229\163\254\154:\2231\135'c2KOIm\153\135\164\214\226?\190\159\201\192\246\227\220\192\172_\181U;|\255\199@\228;\150\240\163X\248\023n\232\142E\180#\003i\028\128\157\210k^\002H\165i\203\b\231M\255*\255J2d\018\246q\t\185\239q\027\235\218\146\255\215\171\240\242 \251\163\030\129\128\018Y{\248\240\158\2311I*\255;\"\147\227\142\165e4\212&k\203N\028\254\001:qL\253\157Qw\228\210\023\236\193K\023\018\170I3N\227\237?q\143\154\196\185HO\255\n\138\212,\217\228\007\217\1516m-\162iK\220X\175\026\239\195h\166\141R\1394\021\153\030\214\172\149\221}\133T\238\1340zAt\031t\018g\136\210O\183[\127o\226\201y\022\228\233\157\214\240;Q=Q\167[\006\154fD\233 \162\247J\151g\007\166)/\231\231\250\231\249\195\130\143\185$\168\023G\025\189\150\024\138\002!\196\003C\186\152c\248\144\026\n[#\150:1\220\169\190Z\180%5jAD\183I\201\194\246\017\161\245\131\179\225V+\141m\225\145\155D2w\146E\165@\002\180E\127X\193\158\127\252\169Dc\151;|-\019\255\186\028\206BPE\254-\b]\186\193V\029M\216\007\187=\2105\203\174\129\143@\024 \1578s\192v\235\174\171\161\228\234\028\152V\131cg9\174\t\233\159\248\233`OP\020\155\160\142N\132\229\229k\169\191\028>\002\224\252\232\222i\154\187\175\224\197\252\015\243\252f\170\023\146&\006\143`X\238.3\bJ\134\171]Y0]\187\252\1308\181\220\182\196\228\189\221\154\255\022\194u\201\249\177_~\222\211\159\235\128\188\213\1356I\199[\167!\215r+C\225\171\187\178\177\148\021\t\153e\030i\007\200\218\212\232\252\128\217\199\174|[OaA5Z\157\151(\029I\172\b\129\030i\030\233Q\155`\234`cA\208fs.ixj\252y\226\\\163F\217\224\219\160\130\2229?\253D\187]\031\006\215%\003k;~\019\167\179\253\14679\147j\176\030n\132d\133*mm\227\218\174\189\141\182\230wC\197\197\237rW\0191\171L\158\178\nD\231\249Ry\130\241\005\251\201\178\178\129*{\244+\165\222\028y\n#\185\180\199\001\137\003\197V\206#\031\249#\155\203\170F\176\251*a\215\243*%#\171\189+D&s\182w\186,\171\167;K\154\230\153\229\180x:\165=\221\178,\239\244\236/\015\247\2073\139\142>=\213\220t\250TM\003MEY\202\248\228&{\165\187\203\190_^\238\\\245\232\136\215\252\011\166-\209\233\246\133\200EJ\210\245,\254\1461@\1679\247;9\028']4\208\2287M\169\161\031\219T\223zg\154=\220\144[\154\232\252c\182HV3;\157&\170\154\224\176\157\180\248lS\178\175\198_\188\191\224\250\254\250\214\243\177\233 \225\168\244\232\017\245N\215\157\234\221\187v\247\2114KL\204\132\139q\147\180\134c+y\205\207Iw)N\179\193>\141(\136\173\025zT\161\003Zk\246\017/O-=\137\1295\197\203Yt\016\014dk\151\230\255\132\217\189\011h\222\028\203l\209\149\230\195\211\180:Tj\nv\006C\005|M\133\003\1921.M#\"6\137\166\207\193\147S\189@\225\026\170c\242\222\227\226\206\223c\129r\222K&\181\199U\191(~q\001\0277\129\005\194^\015*\243e%F\199\157\241\219\1407y\181\155~#\145\175\191q\"Q\224\144\b\127\129*`nu\022\b\129\tg\023\\w\248\221\003\002\224XZ\242\024\192\1848\172Z\128iW\247=\151v\\\238\185\153\147B\161\166d\247\220R\132R5G}\163j\220\202\142\160\211\"\174\190\233|\188\137\210rd\246\t\000_NG^6\194\151N\208\180\024\022\203\000\133\146\229\148\021yS\214\207\237A\161\143R\211U\208\150\r\005I\138Y\130\235\129\020\218\2290\195\220\220\246\012\202\143\252\134\176\2034f\145'\156\155\211\153\175Q\250\240\158\017\221\224\214\133\022\140`\210x\249\173\179s\142\254_3\\\226\146DL\220Y\227\194J\150%u$\182c\168\143\165\248\168\007\237\019\183\000\011D\160\031:3\138x\248\003\184|\137\226<\232\164\160H\024\217J\156j\192\238\146\168D\183E\154\179~\251P\216\161=&P\175\178\245\151\151\177\030\nQ2\188W\190lE\022\209/\149\163\029\137RW'\217V\020`\221d\152\240\208\217\237o\148\190:\014\233\249\227\011\208Vw\127\214\238\196y\226\220\003\180I:\227\219\207\004f[\024#\204f\022\208*0\232\1474\188\218-\158z0\218\174\165\253\244OI^f\251\188\220^\131\145p |J\173\169\000\246Zm\0279\241\184\r%\212\172jcY\215\212*\028\172\255\251\237\191\230O\202\\\158\002\250g\134\157l.\216\237hS\133\177\159\195\144M\247\240J..L\n\242\253\216\016|\180\214\017\163B\178\247\206\020\177\019\203\n\146\002|\137N\235vm@\178\223\235\021\200\157\198\147\003yS\187/M\217;kRN\n" @@ -346,7 +348,7 @@ module Internal = struct | "highlight.pack.js" | "/highlight.pack.js" -> Some [ d_6b9eea5bd2cdd91f629293ab3b8808d1; d_30baf6fb746860926fdd280eefc46735; d_7df05ceea77c14d78f1f1df8f98def4f; d_106b469c9254e3a72af1bc5085256cca; d_67a9b9314f488663d02984b1942caa99; d_8f0b0f289edbab5fa989d7242b5a79c6; d_f87003b823aec0ef15af856b16563ad1; d_139199958def64c23c84b0fd9f061417; d_bef53b9bd37fd12d30b7d98d5c9c3a84; ] | "katex.min.css" | "/katex.min.css" -> Some [ d_2d798108ddda42cb699f6ad4421e720e; d_b128d6f091a42be5d7a929703f09ac36; d_1476b6e94be68e530a90bd0723d69c88; d_e357f75b8a7d9a6031bbdc38adcf1422; d_ad152fcf832897f8629ca758460f3d22; d_7c9075f31df2a532c3135ae327c84a92; ] | "katex.min.js" | "/katex.min.js" -> Some [ d_0c2c3443b618aef3ac4519dd2b159bbe; d_a2070486fb8e9102cd1537ebd1216a96; d_48a6338945c47ceb84d335248c3d6873; d_ad48849637d7c8349cb3e6952d5c8699; d_32baa17e8a53bbd439c58b0d89bc0503; d_c7561e7d22eb89e10083cfba7680012c; d_d04b09d89ef0b9af8a297a3592a2e4b1; d_c0cf7351fa27f73a72840e453c4b15f3; d_fadfd470a088dde5c3755136ac4b6188; d_326148c9e075f26f4dd5ee3862f61cf6; d_a55141bd5690b03d71c9675038f73b3f; d_225bdd9918928e02697ef5570454bf56; d_bf8e1c09c2162b9bb4b6578a59cc8069; d_bb5a8ed07dc95fa6f9f51938da398a35; d_b93e718b1ddefad06d18d9736584ad78; d_e12a510e69c6b3e0210294eedc2c3be3; d_bf043adf1d8ba761903c6f3447bae9d3; d_80ae3e22d162129b593049c0dc7f2407; d_d7b447b6bfc36721f581470728505547; d_92e0c0a734f49413d685531ad3f0a03e; d_cabefc6c9607b95a33af32a8c8832767; d_a03f60fbbac88837b2763d52df2c0820; d_5795c26325c462426548bd12ff6ef7a1; d_c0939c104021af2b0d9b24c7102061f2; d_3a7455b94742964a6cc5e84e314a6cfb; d_dc2a908015f68e5bff245fff4e602604; d_96c4d8e2622ac6552ccf67643b20f09c; d_37935d98135b118d937e895f4bb55add; d_efe21915ced6043dcaa8ff576e7948c7; d_fe0aa5b4043d6894e289163dd38508b7; d_dc29762de1ae6c28b3b3cc202f52ac6f; d_2c5af911fa1596ad2eef3a7e342be949; d_01738333fc004372ab1ae8bc7d370677; d_0d6ec6387686b4173900d29c91f338ee; d_5f9942b4d85184e45b9addfc25ca6fd4; d_105a9e030400f28a404c6badd930fe01; d_79c029f6f746a52f4a8bc8b6280c5c88; d_3a50124eae7017a15bb92024b9f6c8ad; d_d1d8d575696cbb5a4994efc9e2862948; d_a6e92521674c97f4d1bd649490d8a987; d_8f38ae17980f4039d715823515fd56d0; d_a841840589a3efb0465e49e0d8f985b5; d_e33d592534625de6438003412e1d8813; d_5b12b53efc1e6da3a434634e81c2251b; d_c7270ab94b84005c36e6e864e6ea5b10; d_5e57240b8ff6745d663ebd2060201199; d_02c9bc01125e92ce389d2ac93e62d14b; d_0d4c13a0e6487657499a2f37795ab83b; d_8ff622534e1e1348711c11358657050b; d_a8b5fa32242a1d360076af4bdc9dafbe; d_725c52bce5d22dff34816d0cea74cf51; d_a6db9cb29ea27586d2138cf4f8710b12; d_31ee9944b6c75c4351486bc790988371; d_1005d4f63119125aeb03e8a2fa265969; d_9ff5a6ec97f55e01b81f13d9d3f0ff67; d_f361846717ba3e91093152df70d5aab3; d_e462cdcfecbc18ac1f1e447bf1ed3697; d_0d5bde992f9fa1c53103cd024ff5833b; d_1b66f4e8c1fbc1c74875f8da050cc1d0; d_bad0217136fdcd657898ee631bd512d1; d_428c2b0f069b4ffaef294dc85aef1e4b; d_cb988ca0480d611a7c52551adcc9ed48; d_cdc6e947cdb2e0bb7fae7f338ffa12a0; d_f56cd226d59f4d3190a095998f97ac56; d_f5d214c6b91ee7f61f5a433fcdd70682; d_f4caf2cb8610b6735641c064e6453b79; d_da739bd79e1901a19d34fbf2d1a16298; ] - | "odoc.css" | "/odoc.css" -> Some [ d_7a053e62260d74e8005f37b6c843a50e; d_26273b7b4624e2875c9e14c7cb14c111; d_fa492d3f7e09f1bd310e80bf0f4de6b4; d_dace847a98825928714b2dd186cf0e2e; ] + | "odoc.css" | "/odoc.css" -> Some [ d_5ee72be1d823f909a47aa812eb50b6f6; d_0fdc0eeaf87b75b6c50e285b375f4e09; d_d2d82183505374fa41992d8d4c34d47e; d_d9618a035fab5935293da68eab054b9d; d_e9036d3c4fc740175253e5c2fd820e23; ] | _ -> None let file_list = [ "fonts/KaTeX_AMS-Regular.woff2"; "fonts/KaTeX_Caligraphic-Bold.woff2"; "fonts/KaTeX_Caligraphic-Regular.woff2"; "fonts/KaTeX_Fraktur-Bold.woff2"; "fonts/KaTeX_Fraktur-Regular.woff2"; "fonts/KaTeX_Main-Bold.woff2"; "fonts/KaTeX_Main-BoldItalic.woff2"; "fonts/KaTeX_Main-Italic.woff2"; "fonts/KaTeX_Main-Regular.woff2"; "fonts/KaTeX_Math-BoldItalic.woff2"; "fonts/KaTeX_Math-Italic.woff2"; "fonts/KaTeX_SansSerif-Bold.woff2"; "fonts/KaTeX_SansSerif-Italic.woff2"; "fonts/KaTeX_SansSerif-Regular.woff2"; "fonts/KaTeX_Script-Regular.woff2"; "fonts/KaTeX_Size1-Regular.woff2"; "fonts/KaTeX_Size2-Regular.woff2"; "fonts/KaTeX_Size3-Regular.woff2"; "fonts/KaTeX_Size4-Regular.woff2"; "fonts/KaTeX_Typewriter-Regular.woff2"; "highlight.pack.js"; "katex.min.css"; "katex.min.js"; "odoc.css"; ] @@ -383,7 +385,7 @@ let hash = function | "highlight.pack.js" | "/highlight.pack.js" -> Some "0edaf18e63738907db01389ccf15cbc1" | "katex.min.css" | "/katex.min.css" -> Some "1a262c83aa48d3ba34dd01c2ec6087d8" | "katex.min.js" | "/katex.min.js" -> Some "0376fd70eef224e946e13788118db3d1" - | "odoc.css" | "/odoc.css" -> Some "e65986891f8113aee9c7ef66053656fb" + | "odoc.css" | "/odoc.css" -> Some "50239310d5c7e722b901228eadf61c4d" | _ -> None let size = function @@ -410,5 +412,5 @@ let size = function | "highlight.pack.js" | "/highlight.pack.js" -> Some 32934 | "katex.min.css" | "/katex.min.css" -> Some 20978 | "katex.min.js" | "/katex.min.js" -> Some 270376 - | "odoc.css" | "/odoc.css" -> Some 15209 + | "odoc.css" | "/odoc.css" -> Some 16725 | _ -> None diff --git a/src/latex/generator.ml b/src/latex/generator.ml index bd0ea06833..5bb9c2ad3b 100644 --- a/src/latex/generator.ml +++ b/src/latex/generator.ml @@ -405,14 +405,21 @@ and items l = elts |> continue_with rest | Heading h :: rest -> heading h |> continue_with rest | Include - { attr = _; anchor; doc; content = { summary; status = _; content } } + { + attr = _; + source_anchor = _; + anchor; + doc; + content = { summary; status = _; content }; + } :: rest -> let included = items content in let docs = block ~in_source:true doc in let summary = source (inline ~verbatim:false ~in_source:true) summary in let content = included in label anchor @ docs @ summary @ content |> continue_with rest - | Declaration { Item.attr = _; anchor; content; doc } :: rest -> + | Declaration { Item.attr = _; source_anchor = _; anchor; content; doc } + :: rest -> let content = label anchor @ documentedSrc content in let elts = match doc with @@ -459,7 +466,7 @@ module Page = struct List.flatten @@ List.map (subpage ~with_children) subpages and page ~with_children p = - let { Page.preamble; items = i; url } = + let { Page.preamble; items = i; url; _ } = Doctree.Labels.disambiguate_page ~enter_subpages:true p and subpages = subpages ~with_children @@ Doctree.Subpages.compute p in let i = Doctree.Shift.compute ~on_sub i in @@ -469,4 +476,6 @@ module Page = struct page end -let render ~with_children page = [ Page.page ~with_children page ] +let render ~with_children = function + | Document.Page page -> [ Page.page ~with_children page ] + | Source_page _ -> [] diff --git a/src/latex/generator.mli b/src/latex/generator.mli index fe4af047cb..3140da0418 100644 --- a/src/latex/generator.mli +++ b/src/latex/generator.mli @@ -4,5 +4,5 @@ end val render : with_children:bool -> - Odoc_document.Types.Page.t -> + Odoc_document.Types.Document.t -> Odoc_document.Renderer.page list diff --git a/src/loader/cmi.ml b/src/loader/cmi.ml index 817e67a6ef..6d43d62b83 100644 --- a/src/loader/cmi.ml +++ b/src/loader/cmi.ml @@ -14,10 +14,11 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +module Loader_Uid = Uid open Asttypes open Types - module OCamlPath = Path +module Uid = Loader_Uid open Odoc_model.Paths open Odoc_model.Lang @@ -579,6 +580,7 @@ and read_object env fi nm = let read_value_description env parent id vd = let open Signature in let id = Env.find_value_identifier env id in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in @@ -597,7 +599,7 @@ let read_value_description env parent id vd = External primitives | _ -> assert false in - Value { Value.id; doc; type_; value } + Value { Value.id; locs; doc; type_; value } let read_label_declaration env parent ld = let open TypeDecl.Field in @@ -705,6 +707,7 @@ let read_class_constraints env params = let read_type_declaration env parent id decl = let open TypeDecl in let id = Env.find_type_identifier env id in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container decl.type_attributes @@ -735,12 +738,13 @@ let read_type_declaration env parent id decl = in let private_ = (decl.type_private = Private) in let equation = Equation.{params; manifest; constraints; private_} in - {id; doc; canonical; equation; representation} + {id; locs; doc; canonical; equation; representation} let read_extension_constructor env parent id ext = let open Extension.Constructor in let name = Ident.name id in let id = Identifier.Mk.extension(parent, Odoc_model.Names.ExtensionName.make_std name) in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag container ext.ext_attributes in let args = @@ -748,7 +752,7 @@ let read_extension_constructor env parent id ext = (parent : Identifier.Signature.t :> Identifier.Parent.t) ext.ext_args in let res = opt_map (read_type_expr env) ext.ext_ret_type in - {id; doc; args; res} + {id; locs; doc; args; res} let read_type_extension env parent id ext rest = let open Extension in @@ -774,6 +778,7 @@ let read_exception env parent id ext = let open Exception in let name = Ident.name id in let id = Identifier.Mk.exception_(parent, Odoc_model.Names.ExceptionName.make_std name) in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag container ext.ext_attributes in mark_exception ext; @@ -782,7 +787,7 @@ let read_exception env parent id ext = (parent : Identifier.Signature.t :> Identifier.Parent.t) ext.ext_args in let res = opt_map (read_type_expr env) ext.ext_ret_type in - {id; doc; args; res} + {id; locs; doc; args; res} let read_method env parent concrete (name, kind, typ) = let open Method in @@ -867,6 +872,7 @@ let rec read_virtual = function let read_class_type_declaration env parent id cltd = let open ClassType in let id = Env.find_class_type_identifier env id in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag container cltd.clty_attributes in mark_class_type_declaration cltd; @@ -879,7 +885,7 @@ let read_class_type_declaration env parent id cltd = read_class_signature env (id :> Identifier.ClassSignature.t) cltd.clty_params cltd.clty_type in let virtual_ = read_virtual cltd.clty_type in - { id; doc; virtual_; params; expr; expansion = None } + { id; locs; doc; virtual_; params; expr; expansion = None } let rec read_class_type env parent params = let open Class in function @@ -902,6 +908,7 @@ let rec read_class_type env parent params = let read_class_declaration env parent id cld = let open Class in let id = Env.find_class_identifier env id in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag container cld.cty_attributes in mark_class_declaration cld; @@ -914,7 +921,7 @@ let read_class_declaration env parent id cld = read_class_type env (id :> Identifier.ClassSignature.t) cld.cty_params cld.cty_type in let virtual_ = cld.cty_new = None in - { id; doc; virtual_; params; type_; expansion = None } + { id; locs; doc; virtual_; params; type_; expansion = None } let rec read_module_type env parent (mty : Odoc_model.Compat.module_type) = let open ModuleType in @@ -941,15 +948,17 @@ let rec read_module_type env parent (mty : Odoc_model.Compat.module_type) = and read_module_type_declaration env parent id (mtd : Odoc_model.Compat.modtype_declaration) = let open ModuleType in let id = Env.find_module_type env id in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container mtd.mtd_attributes in let canonical = (canonical :> Path.ModuleType.t option) in let expr = opt_map (read_module_type env (id :> Identifier.Signature.t)) mtd.mtd_type in - {id; doc; canonical; expr } + {id; locs; doc; canonical; expr } and read_module_declaration env parent ident (md : Odoc_model.Compat.module_declaration) = let open Module in let id = (Env.find_module_identifier env ident :> Identifier.Module.t) in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container md.md_attributes in let canonical = (canonical :> Path.Module.t option) in @@ -963,7 +972,7 @@ and read_module_declaration env parent ident (md : Odoc_model.Compat.module_decl | Some _ -> false | None -> Odoc_model.Root.contains_double_underscore (Ident.name ident) in - {id; doc; type_; canonical; hidden } + {id; locs; doc; type_; canonical; hidden } and read_type_rec_status rec_status = let open Signature in diff --git a/src/loader/cmi.mli b/src/loader/cmi.mli index 1c9fae91ef..23768302d0 100644 --- a/src/loader/cmi.mli +++ b/src/loader/cmi.mli @@ -18,7 +18,6 @@ module Paths = Odoc_model.Paths - val read_interface : Odoc_model.Paths.Identifier.ContainerPage.t option -> string -> diff --git a/src/loader/cmt.ml b/src/loader/cmt.ml index 41b89c8cc0..31a8786e7b 100644 --- a/src/loader/cmt.ml +++ b/src/loader/cmt.ml @@ -14,8 +14,8 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) + open Asttypes -open Types open Typedtree module OCamlPath = Path @@ -25,11 +25,11 @@ open Odoc_model.Lang module Env = Ident_env - let read_core_type env ctyp = Cmi.read_type_expr env ctyp.ctyp_type let rec read_pattern env parent doc pat = + let locs _id = None in let open Signature in match pat.pat_desc with | Tpat_any -> [] @@ -39,14 +39,14 @@ let rec read_pattern env parent doc pat = Cmi.mark_type_expr pat.pat_type; let type_ = Cmi.read_type_expr env pat.pat_type in let value = Abstract in - [Value {id; doc; type_; value}] + [Value {id; locs = locs id; doc; type_; value}] | Tpat_alias(pat, id, _) -> let open Value in let id = Env.find_value_identifier env id in Cmi.mark_type_expr pat.pat_type; let type_ = Cmi.read_type_expr env pat.pat_type in let value = Abstract in - Value {id; doc; type_; value} :: read_pattern env parent doc pat + Value {id; locs = locs id; doc; type_; value} :: read_pattern env parent doc pat | Tpat_constant _ -> [] | Tpat_tuple pats -> List.concat (List.map (read_pattern env parent doc) pats) @@ -111,7 +111,7 @@ let read_type_extension env parent tyext = in let type_params = List.map - (Cmi.read_type_parameter false Variance.null) + (Cmi.read_type_parameter false Types.Variance.null) type_params in let private_ = (tyext.tyext_private = Private) in @@ -122,7 +122,7 @@ let read_type_extension env parent tyext = env parent ext.ext_id ext.ext_type) tyext.tyext_constructors in - { parent; type_path; doc; type_params; private_; constructors; } + { parent; type_path; doc; type_params; private_; constructors; } (** Make a standalone comment out of a comment attached to an item that isn't rendered. For example, [constraint] items are read separately and not @@ -324,6 +324,7 @@ let rec read_class_expr env parent params cl = let read_class_declaration env parent cld = let open Class in let id = Env.find_class_identifier env cld.ci_id_class in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag container cld.ci_attributes in Cmi.mark_class_declaration cld.ci_decl; @@ -333,11 +334,11 @@ let read_class_declaration env parent cld = in let params = List.map - (Cmi.read_type_parameter false Variance.null) + (Cmi.read_type_parameter false Types.Variance.null) clparams in let type_ = read_class_expr env (id :> Identifier.ClassSignature.t) clparams cld.ci_expr in - { id; doc; virtual_; params; type_; expansion = None } + { id; locs; doc; virtual_; params; type_; expansion = None } let read_class_declarations env parent clds = let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in @@ -428,6 +429,7 @@ and read_module_binding env parent mb = let id = Env.find_module_identifier env mb.mb_id in #endif let id = (id :> Identifier.Module.t) in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container mb.mb_attributes in let type_, canonical = @@ -452,7 +454,7 @@ and read_module_binding env parent mb = | _ -> false #endif in - Some {id; doc; type_; canonical; hidden; } + Some {id; locs; doc; type_; canonical; hidden; } and read_module_bindings env parent mbs = let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) diff --git a/src/loader/cmti.ml b/src/loader/cmti.ml index d5d205172d..4a6391197f 100644 --- a/src/loader/cmti.ml +++ b/src/loader/cmti.ml @@ -146,6 +146,7 @@ let rec read_core_type env container ctyp = let read_value_description env parent vd = let open Signature in let id = Env.find_value_identifier env vd.val_id in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in @@ -156,7 +157,7 @@ let read_value_description env parent vd = | [] -> Value.Abstract | primitives -> External primitives in - Value { Value.id; doc; type_; value } + Value { Value.id; locs; doc; type_; value } let read_type_parameter (ctyp, var_and_injectivity) = let open TypeDecl in @@ -256,12 +257,13 @@ let read_type_equation env container decl = let read_type_declaration env parent decl = let open TypeDecl in let id = Env.find_type_identifier env decl.typ_id in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container decl.typ_attributes in let canonical = (canonical :> Path.Type.t option) in let equation = read_type_equation env container decl in let representation = read_type_kind env (id :> Identifier.DataType.t) decl.typ_kind in - {id; doc; canonical; equation; representation} + {id; locs; doc; canonical; equation; representation} let read_type_declarations env parent rec_flag decls = let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in @@ -293,6 +295,7 @@ let read_extension_constructor env parent ext = let open Odoc_model.Names in let name = Ident.name ext.ext_id in let id = Identifier.Mk.extension(parent, ExtensionName.make_std name) in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.Parent.t) in let label_container = (container :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag label_container ext.ext_attributes in @@ -308,7 +311,7 @@ let read_extension_constructor env parent ext = env container label_container args in let res = opt_map (read_core_type env label_container) res in - {id; doc; args; res} + {id; locs; doc; args; res} let read_type_extension env parent tyext = let open Extension in @@ -327,6 +330,7 @@ let read_exception env parent (ext : extension_constructor) = let open Odoc_model.Names in let name = Ident.name ext.ext_id in let id = Identifier.Mk.exception_(parent, ExceptionName.make_std name) in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.Parent.t) in let label_container = (container :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag label_container ext.ext_attributes in @@ -342,7 +346,7 @@ let read_exception env parent (ext : extension_constructor) = env container label_container args in let res = opt_map (read_core_type env label_container) res in - {id; doc; args; res} + {id; locs; doc; args; res} let rec read_class_type_field env parent ctf = let open ClassSignature in @@ -416,12 +420,13 @@ and read_class_signature env parent label_parent cltyp = let read_class_type_declaration env parent cltd = let open ClassType in let id = Env.find_class_type_identifier env cltd.ci_id_class_type in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag container cltd.ci_attributes in let virtual_ = (cltd.ci_virt = Virtual) in let params = List.map read_type_parameter cltd.ci_params in let expr = read_class_signature env (id :> Identifier.ClassSignature.t) container cltd.ci_expr in - { id; doc; virtual_; params; expr; expansion = None } + { id; locs; doc; virtual_; params; expr; expansion = None } let read_class_type_declarations env parent cltds = let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in @@ -454,12 +459,13 @@ let rec read_class_type env parent label_parent cty = let read_class_description env parent cld = let open Class in let id = Env.find_class_identifier env cld.ci_id_class in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc = Doc_attr.attached_no_tag container cld.ci_attributes in let virtual_ = (cld.ci_virt = Virtual) in let params = List.map read_type_parameter cld.ci_params in let type_ = read_class_type env (id :> Identifier.ClassSignature.t) container cld.ci_expr in - { id; doc; virtual_; params; type_; expansion = None } + { id; locs; doc; virtual_; params; type_; expansion = None } let read_class_descriptions env parent clds = let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in @@ -583,6 +589,7 @@ and read_module_type_maybe_canonical env parent container ~canonical mty = and read_module_type_declaration env parent mtd = let open ModuleType in let id = Env.find_module_type env mtd.mtd_id in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container mtd.mtd_attributes in let expr, canonical = @@ -597,7 +604,7 @@ and read_module_type_declaration env parent mtd = | None -> (None, canonical) in let canonical = (canonical :> Path.ModuleType.t option) in - { id; doc; canonical; expr } + { id; locs; doc; canonical; expr } and read_module_declaration env parent md = let open Module in @@ -610,6 +617,7 @@ and read_module_declaration env parent md = let id = Env.find_module_identifier env md.md_id in #endif let id = (id :> Identifier.Module.t) in + let locs = None in let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container md.md_attributes in let type_, canonical = @@ -635,7 +643,7 @@ and read_module_declaration env parent md = | _ -> false #endif in - Some {id; doc; type_; canonical; hidden} + Some {id; locs; doc; type_; canonical; hidden} and read_module_declarations env parent mds = let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in diff --git a/src/loader/dune b/src/loader/dune index f40d3d4055..ebb633480c 100644 --- a/src/loader/dune +++ b/src/loader/dune @@ -22,4 +22,4 @@ (preprocess (action (run %{bin:cppo} -V OCAML:%{ocaml_version} %{input-file}))) - (libraries compiler-libs.common odoc_model odoc-parser)) + (libraries odoc_model odoc-parser syntax_highlighter)) diff --git a/src/loader/local_jmp.ml b/src/loader/local_jmp.ml new file mode 100644 index 0000000000..6c37944912 --- /dev/null +++ b/src/loader/local_jmp.ml @@ -0,0 +1,80 @@ +#if OCAML_VERSION >= (4, 14, 0) + +open Odoc_model.Lang.Source_info + +let pos_of_loc loc = (loc.Location.loc_start.pos_cnum, loc.loc_end.pos_cnum) + +let ( let= ) m f = match m with Some x -> f x | None -> () + +module Local_analysis = struct + let expr poses expr = + match expr with + | { Typedtree.exp_desc = Texp_ident (Pident id, _, _); exp_loc; _ } + when not exp_loc.loc_ghost -> + let anchor = Ident.unique_name id in + poses := (Occurence { anchor }, pos_of_loc exp_loc) :: !poses + | _ -> () + let pat poses (type a) : a Typedtree.general_pattern -> unit = function + | { + pat_desc = Tpat_var (id, _stringloc) | Tpat_alias (_, id, _stringloc); + pat_loc; + _; + } + when not pat_loc.loc_ghost -> + let uniq = Ident.unique_name id in + poses := (Def uniq, pos_of_loc pat_loc) :: !poses + | _ -> () +end + +module Global_analysis = struct + let anchor_of_uid uid = + match Uid.unpack_uid (Uid.of_shape_uid uid) with + | Some (_, Some id) -> Some (Uid.anchor_of_id id) + | _ -> None + + (** Generate the anchors that will be pointed to by [lookup_def]. *) + let init poses uid_to_loc = + Shape.Uid.Tbl.iter + (fun uid t -> + let= s = anchor_of_uid uid in + poses := (Def s, pos_of_loc t) :: !poses) + uid_to_loc + + let expr poses uid_to_loc expr = + match expr with + | { Typedtree.exp_desc = Texp_ident (_, _, value_description); exp_loc; _ } + -> + (* Only generate anchor if the uid is in the location table. We don't + link to modules outside of the compilation unit. *) + let= _ = Shape.Uid.Tbl.find_opt uid_to_loc value_description.val_uid in + let= anchor = anchor_of_uid value_description.val_uid in + poses := (Occurence { anchor }, pos_of_loc exp_loc) :: !poses + | _ -> () +end + +let of_cmt (cmt : Cmt_format.cmt_infos) = + let ttree = cmt.cmt_annots in + match ttree with + | Cmt_format.Implementation structure -> + let uid_to_loc = cmt.cmt_uid_to_loc in + let poses = ref [] in + Global_analysis.init poses uid_to_loc; + let expr iterator expr = + Local_analysis.expr poses expr; + Global_analysis.expr poses uid_to_loc expr; + Tast_iterator.default_iterator.expr iterator expr + in + let pat iterator pat = + Local_analysis.pat poses pat; + Tast_iterator.default_iterator.pat iterator pat + in + let iterator = { Tast_iterator.default_iterator with expr; pat } in + iterator.structure iterator structure; + !poses + | _ -> [] + +#else + +let of_cmt _ = [] + +#endif diff --git a/src/loader/local_jmp.mli b/src/loader/local_jmp.mli new file mode 100644 index 0000000000..bc3c1f4c50 --- /dev/null +++ b/src/loader/local_jmp.mli @@ -0,0 +1 @@ +val of_cmt : Cmt_format.cmt_infos -> Source_info.local_jmp_infos diff --git a/src/loader/lookup_def.ml b/src/loader/lookup_def.ml new file mode 100644 index 0000000000..da679e7a52 --- /dev/null +++ b/src/loader/lookup_def.ml @@ -0,0 +1,84 @@ +#if OCAML_VERSION >= (4, 14, 0) + +open Odoc_model +open Odoc_model.Paths +open Odoc_model.Names +module Kind = Shape.Sig_component_kind + +let ( >>= ) m f = match m with Some x -> f x | None -> None + +type t = Shape.t + +(** Project an identifier into a shape. *) +let rec shape_of_id lookup_shape : + [< Identifier.t_pv ] Identifier.id -> Shape.t option = + let proj parent kind name = + let item = Shape.Item.make name kind in + match shape_of_id lookup_shape (parent :> Identifier.t) with + | Some shape -> Some (Shape.proj shape item) + | None -> None + in + fun id -> + match id.iv with + | `Root (_, name) -> + lookup_shape (ModuleName.to_string name) >>= fun (_, shape) -> + Some shape + | `Module (parent, name) -> + proj parent Kind.Module (ModuleName.to_string name) + | `Result parent -> + (* Apply the functor to an empty signature. This doesn't seem to cause + any problem, as the shape would stop resolve on an item inside the + result of the function, which is what we want. *) + shape_of_id lookup_shape (parent :> Identifier.t) >>= fun parent -> + Some (Shape.app parent ~arg:(Shape.str Shape.Item.Map.empty)) + | `ModuleType (parent, name) -> + proj parent Kind.Module_type (ModuleTypeName.to_string name) + | `Type (parent, name) -> proj parent Kind.Type (TypeName.to_string name) + | `Value (parent, name) -> proj parent Kind.Value (ValueName.to_string name) + | `Extension (parent, name) -> + proj parent Kind.Extension_constructor (ExtensionName.to_string name) + | `Exception (parent, name) -> + proj parent Kind.Extension_constructor (ExceptionName.to_string name) + | `Class (parent, name) -> proj parent Kind.Class (ClassName.to_string name) + | `ClassType (parent, name) -> + proj parent Kind.Class_type (ClassTypeName.to_string name) + | `Page _ | `LeafPage _ | `Label _ | `CoreType _ | `CoreException _ + | `Constructor _ | `Field _ | `Method _ | `InstanceVariable _ | `Parameter _ + -> + (* Not represented in shapes. *) + None + +module MkId = Identifier.Mk + +let lookup_def lookup_unit id = + match shape_of_id lookup_unit id with + | None -> None + | Some query -> + let module Reduce = Shape.Make_reduce (struct + type env = unit + let fuel = 10 + let read_unit_shape ~unit_name = + match lookup_unit unit_name with + | Some (_, shape) -> Some shape + | None -> None + let find_shape _ _ = raise Not_found + end) in + let result = try Some (Reduce.reduce () query) with Not_found -> None in + result >>= fun result -> + result.uid >>= fun uid -> + Uid.unpack_uid (Uid.of_shape_uid uid) >>= fun (unit_name, id) -> + lookup_unit unit_name >>= fun (unit, _) -> + unit.Lang.Compilation_unit.source_info >>= fun sources -> + let anchor = id >>= fun id -> Some (Uid.anchor_of_id id) in + Some { Lang.Locations.source_parent = sources.id; anchor } + +let of_cmt (cmt : Cmt_format.cmt_infos) = cmt.cmt_impl_shape + +#else + +type t = unit + +let lookup_def _ _id = None +let of_cmt _ = Some () + +#endif diff --git a/src/loader/lookup_def.mli b/src/loader/lookup_def.mli new file mode 100644 index 0000000000..9148ef2d5e --- /dev/null +++ b/src/loader/lookup_def.mli @@ -0,0 +1,17 @@ +open Odoc_model +open Paths +type t + +val lookup_def : + (string -> (Lang.Compilation_unit.t * t) option) -> + Identifier.t -> + Lang.Locations.t option +(** Returns the root module containing the definition of the given identifier + and the corresponding anchor. *) + +val of_cmt : Cmt_format.cmt_infos -> t option +(** Returns [None] if the cmt doesn't have a shape (eg. if it is not an + implementation). Returns [Some _] even if shapes are not implemented. + + In case of [Some _], returns both the shape and the relevant infos taken + from the [cmt]. *) diff --git a/src/loader/odoc_loader.ml b/src/loader/odoc_loader.ml index 38c7d08371..f29961e476 100644 --- a/src/loader/odoc_loader.ml +++ b/src/loader/odoc_loader.ml @@ -1,6 +1,9 @@ open Result module Error = Odoc_model.Error +module Lookup_def = Lookup_def +module Source_info = Source_info + let read_string parent_definition filename text = let location = let pos = @@ -29,6 +32,11 @@ let wrong_version file = let error_msg file (msg : string) = Error.raise_exception (Error.filename_only "%s" msg file) +type make_root = + module_name:string -> + digest:Digest.t -> + (Odoc_model.Root.t, [ `Msg of string ]) result + exception Corrupted exception Not_an_implementation @@ -37,6 +45,22 @@ exception Not_an_interface exception Make_root_error of string +(** [cmt_info.cmt_annots = Implementation _] *) +let read_cmt_infos' cmt_info = + match Lookup_def.of_cmt cmt_info with + | None -> None + | Some shape -> + let jmp_infos = Local_jmp.of_cmt cmt_info in + Some (shape, jmp_infos) + +let read_cmt_infos ~filename () = + match Cmt_format.read_cmt filename with + | exception Cmi_format.Error _ -> raise Corrupted + | cmt_info -> ( + match cmt_info.cmt_annots with + | Implementation _ -> read_cmt_infos' cmt_info + | _ -> raise Not_an_implementation) + let make_compilation_unit ~make_root ~imports ~interface ?sourcefile ~name ~id ?canonical content = let open Odoc_model.Lang.Compilation_unit in @@ -74,6 +98,7 @@ let make_compilation_unit ~make_root ~imports ~interface ?sourcefile ~name ~id expansion = None; linked = false; canonical; + source_info = None; } let compilation_unit_of_sig ~make_root ~imports ~interface ?sourcefile ~name ~id @@ -139,12 +164,14 @@ let read_cmt ~make_root ~parent ~filename () = items in let content = Odoc_model.Lang.Compilation_unit.Pack items in - make_compilation_unit ~make_root ~imports ~interface ~sourcefile ~name - ~id content + ( make_compilation_unit ~make_root ~imports ~interface ~sourcefile + ~name ~id content, + None ) | Implementation impl -> let id, sg, canonical = Cmt.read_implementation parent name impl in - compilation_unit_of_sig ~make_root ~imports ~interface ~sourcefile - ~name ~id ?canonical sg + ( compilation_unit_of_sig ~make_root ~imports ~interface ~sourcefile + ~name ~id ?canonical sg, + read_cmt_infos' cmt_info ) | _ -> raise Not_an_implementation) let read_cmi ~make_root ~parent ~filename () = @@ -171,6 +198,8 @@ let wrap_errors ~filename f = | Not_an_interface -> not_an_interface filename | Make_root_error m -> error_msg filename m) +let read_cmt_infos ~filename = wrap_errors ~filename (read_cmt_infos ~filename) + let read_cmti ~make_root ~parent ~filename = wrap_errors ~filename (read_cmti ~make_root ~parent ~filename) @@ -179,3 +208,5 @@ let read_cmt ~make_root ~parent ~filename = let read_cmi ~make_root ~parent ~filename = wrap_errors ~filename (read_cmi ~make_root ~parent ~filename) + +let read_location = Doc_attr.read_location diff --git a/src/loader/odoc_loader.mli b/src/loader/odoc_loader.mli index d0c6e27a70..91fb4b7a42 100644 --- a/src/loader/odoc_loader.mli +++ b/src/loader/odoc_loader.mli @@ -1,5 +1,14 @@ open Result open Odoc_model +open Odoc_model.Paths + +module Lookup_def = Lookup_def +module Source_info = Source_info + +type make_root = + module_name:string -> + digest:Digest.t -> + (Odoc_model.Root.t, [ `Msg of string ]) result val read_string : Paths.Identifier.LabelParent.t -> @@ -7,29 +16,32 @@ val read_string : string -> (Comment.docs_or_stop, Error.t) result Error.with_warnings +val read_cmt_infos : + filename:string -> + ((Lookup_def.t * Source_info.local_jmp_infos) option, Error.t) result + Error.with_warnings +(** Read the shape from a .cmt file. *) + val read_cmti : - make_root: - (module_name:string -> - digest:Digest.t -> - (Odoc_model.Root.t, [ `Msg of string ]) result) -> - parent:Odoc_model.Paths.Identifier.ContainerPage.t option -> + make_root:make_root -> + parent:Identifier.ContainerPage.t option -> filename:string -> (Lang.Compilation_unit.t, Error.t) result Error.with_warnings val read_cmt : - make_root: - (module_name:string -> - digest:Digest.t -> - (Odoc_model.Root.t, [ `Msg of string ]) result) -> - parent:Odoc_model.Paths.Identifier.ContainerPage.t option -> + make_root:make_root -> + parent:Identifier.ContainerPage.t option -> filename:string -> - (Lang.Compilation_unit.t, Error.t) result Error.with_warnings + ( Lang.Compilation_unit.t * (Lookup_def.t * Source_info.local_jmp_infos) option, + Error.t ) + result + Error.with_warnings +(** The shape is not returned in case of a pack. *) val read_cmi : - make_root: - (module_name:string -> - digest:Digest.t -> - (Odoc_model.Root.t, [ `Msg of string ]) result) -> - parent:Odoc_model.Paths.Identifier.ContainerPage.t option -> + make_root:make_root -> + parent:Identifier.ContainerPage.t option -> filename:string -> (Lang.Compilation_unit.t, Error.t) result Error.with_warnings + +val read_location : Location.t -> Location_.span diff --git a/src/loader/source_info.ml b/src/loader/source_info.ml new file mode 100644 index 0000000000..584ea5ae39 --- /dev/null +++ b/src/loader/source_info.ml @@ -0,0 +1,11 @@ +open Odoc_model.Lang.Source_info + +type local_jmp_infos = jmp_to_def with_pos list + +let of_local_jmp local_jmp = + List.rev_map (fun (jmp, pos) -> (Local_jmp jmp, pos)) local_jmp + +let of_source src = + Syntax_highlighter.syntax_highlighting_locs src + |> List.rev_map (fun (x, y) -> (Syntax x, y)) +(* The order won't matter and input can be large *) diff --git a/src/loader/source_info.mli b/src/loader/source_info.mli new file mode 100644 index 0000000000..da415ca100 --- /dev/null +++ b/src/loader/source_info.mli @@ -0,0 +1,9 @@ +open Odoc_model.Lang.Source_info + +type local_jmp_infos = jmp_to_def with_pos list + +val of_local_jmp : local_jmp_infos -> infos +(** Source infos loaded from the cmt file. *) + +val of_source : string -> infos +(** Source infos parsed from the source code. *) diff --git a/src/loader/uid.ml b/src/loader/uid.ml new file mode 100644 index 0000000000..48a25c3364 --- /dev/null +++ b/src/loader/uid.ml @@ -0,0 +1,40 @@ +type id = string + +let anchor_of_id id = "def-" ^ id + +#if OCAML_VERSION >= (4, 14, 0) + +open Types + +type uid = Shape.Uid.t + +let unpack_uid uid = + match uid with + | Shape.Uid.Compilation_unit s -> Some (s, None) + | Item { comp_unit; id } -> Some (comp_unit, Some (string_of_int id)) + | Predef _ -> None + | Internal -> None + +let of_value_description vd = Some vd.val_uid +let of_type_declaration decl = Some decl.type_uid +let of_extension_constructor ext = Some ext.ext_uid +let of_class_type_declaration cltd = Some cltd.clty_uid +let of_class_declaration cld = Some cld.cty_uid +let of_module_type_declaration mtd = Some mtd.mtd_uid + +let of_shape_uid uid = uid + +#else + +type uid = unit + +let unpack_uid () = None + +let of_value_description _vd = None +let of_type_declaration _decl = None +let of_extension_constructor _ext = None +let of_class_type_declaration _cltd = None +let of_class_declaration _cld = None +let of_module_type_declaration _mtd = None + +#endif diff --git a/src/loader/uid.mli b/src/loader/uid.mli new file mode 100644 index 0000000000..ce4e1ca29e --- /dev/null +++ b/src/loader/uid.mli @@ -0,0 +1,23 @@ +open Types + +type uid +type id + +val anchor_of_id : id -> string +(** Returns the anchor that will be used to link to the [id]. *) + +val unpack_uid : uid -> (string * id option) option +(** [unpack_uid uid] unpacks a [uid] into [Some (comp_unit, id)] *) + +val of_value_description : value_description -> uid option +val of_type_declaration : type_declaration -> uid option +val of_extension_constructor : extension_constructor -> uid option +val of_class_type_declaration : class_type_declaration -> uid option +val of_class_declaration : class_declaration -> uid option +val of_module_type_declaration : modtype_declaration -> uid option + +#if OCAML_VERSION >= (4, 14, 0) + +val of_shape_uid : Shape.Uid.t -> uid + +#endif diff --git a/src/manpage/generator.ml b/src/manpage/generator.ml index ca1f45d9d4..bd6c895439 100644 --- a/src/manpage/generator.ml +++ b/src/manpage/generator.ml @@ -357,7 +357,7 @@ let next_heading, reset_heading = and reset () = heading_stack := [] in (next, reset) -let heading ~nested { Heading.label = _; level; title } = +let heading ~nested { Heading.label = _; level; title; source_anchor = _ } = let prefix = if level = 0 then noop else if level <= 3 then str "%s " (next_heading level) @@ -431,7 +431,7 @@ let rec documentedSrc (l : DocumentedSrc.t) = let l = list ~sep:break (List.map f lines) in indent 2 (break ++ l) ++ break_if_nonempty rest ++ continue rest) -and subpage { preamble = _; items; url = _ } = +and subpage { preamble = _; items; url = _; _ } = let content = items in let surround body = if content = [] then sp else indent 2 (break ++ body) ++ break @@ -450,7 +450,7 @@ and item ~nested (l : Item.t list) = | Heading h -> let h = heading ~nested h in vspace ++ h ++ vspace ++ item ~nested rest - | Declaration { attr = _; anchor = _; content; doc } -> + | Declaration { attr = _; anchor = _; source_anchor = _; content; doc } -> let decl = documentedSrc content in let doc = match doc with @@ -459,8 +459,13 @@ and item ~nested (l : Item.t list) = in decl ++ doc ++ continue rest | Include - { attr = _; anchor = _; content = { summary; status; content }; doc } - -> + { + attr = _; + anchor = _; + source_anchor = _; + content = { summary; status; content }; + doc; + } -> let d = if inline_subpage status then item ~nested content else @@ -491,11 +496,15 @@ let page p = let rec subpage subp = let p = subp.Subpage.content in - if Link.should_inline p.url then [] else [ render p ] + if Link.should_inline p.url then [] else [ render_page p ] -and render (p : Page.t) = +and render_page (p : Page.t) = let p = Doctree.Labels.disambiguate_page ~enter_subpages:true p and children = Utils.flatmap ~f:subpage @@ Subpages.compute p in let content ppf = Format.fprintf ppf "%a@." Roff.pp (page p) in let filename = Link.as_filename p.url in { Renderer.filename; content; children } + +let render = function + | Document.Page page -> [ render_page page ] + | Source_page _ -> [] diff --git a/src/manpage/generator.mli b/src/manpage/generator.mli index 3d87bdb3f1..4d80e7664c 100644 --- a/src/manpage/generator.mli +++ b/src/manpage/generator.mli @@ -1 +1 @@ -val render : Odoc_document.Types.Page.t -> Odoc_document.Renderer.page +val render : Odoc_document.Types.Document.t -> Odoc_document.Renderer.page list diff --git a/src/model/lang.ml b/src/model/lang.ml index 567b64f122..2544f0fdc8 100644 --- a/src/model/lang.ml +++ b/src/model/lang.ml @@ -16,6 +16,30 @@ open Paths +module Locations = struct + type t = { + source_parent : Identifier.SourcePage.t; + (** Correspond to where the source code is stored. Might be different + from the root component of the identifier inside expansions. *) + anchor : string option; + (** Location of the definition in the implementation file. *) + } +end + +module Source_info = struct + type anchor = { anchor : string } + + type jmp_to_def = Occurence of anchor | Def of string + + type info = Syntax of string | Local_jmp of jmp_to_def + + type 'a with_pos = 'a * (int * int) + + type infos = info with_pos list + + type t = { id : Identifier.SourcePage.t; infos : infos } +end + (** {3 Modules} *) module rec Module : sig @@ -25,6 +49,8 @@ module rec Module : sig type t = { id : Identifier.Module.t; + locs : Locations.t option; + (** Locations might not be set when the module is artificially constructed from a functor argument. *) doc : Comment.docs; type_ : decl; canonical : Path.Module.t option; @@ -101,6 +127,8 @@ and ModuleType : sig type t = { id : Identifier.ModuleType.t; + locs : Locations.t option; + (** Can be [None] for module types created by a type substitution. *) doc : Comment.docs; canonical : Path.ModuleType.t option; expr : expr option; @@ -240,6 +268,7 @@ and TypeDecl : sig type t = { id : Identifier.Type.t; + locs : Locations.t option; doc : Comment.docs; canonical : Path.Type.t option; equation : Equation.t; @@ -254,6 +283,7 @@ and Extension : sig module Constructor : sig type t = { id : Identifier.Extension.t; + locs : Locations.t option; doc : Comment.docs; args : TypeDecl.Constructor.argument; res : TypeExpr.t option; @@ -275,6 +305,7 @@ end = and Exception : sig type t = { id : Identifier.Exception.t; + locs : Locations.t option; doc : Comment.docs; args : TypeDecl.Constructor.argument; res : TypeExpr.t option; @@ -289,9 +320,10 @@ and Value : sig type t = { id : Identifier.Value.t; + locs : Locations.t option; + value : value; doc : Comment.docs; type_ : TypeExpr.t; - value : value; } end = Value @@ -305,6 +337,7 @@ and Class : sig type t = { id : Identifier.Class.t; + locs : Locations.t option; doc : Comment.docs; virtual_ : bool; params : TypeDecl.param list; @@ -323,6 +356,7 @@ and ClassType : sig type t = { id : Identifier.ClassType.t; + locs : Locations.t option; doc : Comment.docs; virtual_ : bool; params : TypeDecl.param list; @@ -464,22 +498,38 @@ module rec Compilation_unit : sig expansion : Signature.t option; linked : bool; (** Whether this unit has been linked. *) canonical : Path.Module.t option; + source_info : Source_info.t option; } end = Compilation_unit module rec Page : sig + type child = + | Page_child of string + | Module_child of string + | Source_tree_child of string + type t = { name : Identifier.Page.t; root : Root.t; content : Comment.docs; - children : Reference.t list; + children : child list; digest : Digest.t; linked : bool; } end = Page +module rec SourceTree : sig + type t = { + name : Identifier.Page.t; + root : Root.t; + source_children : Identifier.SourcePage.t list; + digest : Digest.t; + } +end = + SourceTree + let umty_of_mty : ModuleType.expr -> ModuleType.U.expr option = function | Signature sg -> Some (Signature sg) | Path { p_path; _ } -> Some (Path p_path) diff --git a/src/model/paths.ml b/src/model/paths.ml index 22cd005145..c688e17a8b 100644 --- a/src/model/paths.ml +++ b/src/model/paths.ml @@ -14,6 +14,9 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +module Ocaml_ident = Ident +module Ocaml_env = Env + open Names module Identifier = struct @@ -49,6 +52,28 @@ module Identifier = struct let name : [< t_pv ] id -> string = fun n -> name_aux (n :> t) + let rec root id = + match id.iv with + | `Root _ as root -> Some { id with iv = root } + | `Module (parent, _) -> root (parent :> t) + | `Parameter (parent, _) -> root (parent :> t) + | `Result x -> root (x :> t) + | `ModuleType (parent, _) -> root (parent :> t) + | `Type (parent, _) -> root (parent :> t) + | `Constructor (parent, _) -> root (parent :> t) + | `Field (parent, _) -> root (parent :> t) + | `Extension (parent, _) -> root (parent :> t) + | `Exception (parent, _) -> root (parent :> t) + | `Value (parent, _) -> root (parent :> t) + | `Class (parent, _) -> root (parent :> t) + | `ClassType (parent, _) -> root (parent :> t) + | `Method (parent, _) -> root (parent :> t) + | `InstanceVariable (parent, _) -> root (parent :> t) + | `Label (parent, _) -> root (parent :> t) + | `Page _ | `LeafPage _ | `CoreType _ | `CoreException _ -> None + + let root id = root (id :> t) + let rec label_parent_aux = let open Paths_types.Identifier in fun (n : any) -> @@ -104,6 +129,20 @@ module Identifier = struct let hash = hash let compare = compare + + let rec root = function + | { iv = `Root _; _ } as root -> root + | { + iv = + ( `ModuleType (parent, _) + | `Module (parent, _) + | `Parameter (parent, _) ); + _; + } -> + root parent + | { iv = `Result x; _ } -> root x + + let root id = root (id :> t) end module ClassSignature = struct @@ -164,6 +203,8 @@ module Identifier = struct let hash = hash let compare = compare + + let name { iv = `Root (_, name); _ } = ModuleName.to_string name end module Module = struct @@ -176,6 +217,8 @@ module Identifier = struct let hash = hash let compare = compare + + let root id = Signature.root (id :> Signature.t) end module FunctorParameter = struct @@ -370,6 +413,26 @@ module Identifier = struct let compare = compare end + module SourceDir = struct + type t = Paths_types.Identifier.source_dir + type t_pv = Paths_types.Identifier.source_dir_pv + let equal = equal + let hash = hash + let compare = compare + let rec name = function + | { iv = `SourceDir (p, n); _ } -> name p ^ n ^ "/" + | { iv = `SourceRoot _; _ } -> "./" + end + + module SourcePage = struct + type t = Paths_types.Identifier.source_page + type t_pv = Paths_types.Identifier.source_page_pv + let equal = equal + let hash = hash + let compare = compare + let name { iv = `SourcePage (p, name); _ } = SourceDir.name p ^ name + end + module OdocId = struct type t = Paths_types.Identifier.odoc_id @@ -393,6 +456,8 @@ module Identifier = struct let hash = hash let compare = compare + + let root id = Signature.root (id :> Signature.t) end module ModuleType = struct @@ -481,6 +546,33 @@ module Identifier = struct [> `LeafPage of ContainerPage.t option * PageName.t ] id = mk_parent_opt PageName.to_string "lp" (fun (p, n) -> `LeafPage (p, n)) + let source_page (container_page, path) = + let rec source_dir dir = + match dir with + | [] -> + mk_parent + (fun () -> "") + "sr" + (fun (p, ()) -> `SourceRoot p) + (container_page, ()) + | a :: q -> + let parent = source_dir q in + mk_parent + (fun k -> k) + "sd" + (fun (p, dir) -> `SourceDir (p, dir)) + (parent, a) + in + match List.rev path with + | [] -> assert false + | file :: dir -> + let parent = source_dir dir in + mk_parent + (fun x -> x) + "sp" + (fun (p, rp) -> `SourcePage (p, rp)) + (parent, file) + let root : ContainerPage.t option * ModuleName.t -> [> `Root of ContainerPage.t option * ModuleName.t ] id = @@ -695,6 +787,20 @@ module Path = struct | `Apply (m, _) -> r m | `Alias (dest, _src) -> r dest | `OpaqueModule m -> r m + + let rec root : t -> string option = function + | `Identifier id -> ( + match Identifier.root (id :> Identifier.t) with + | Some root -> Some (Identifier.name root) + | None -> None) + | `Subst (_, p) + | `Hidden p + | `Module (p, _) + | `Canonical (p, _) + | `Apply (p, _) + | `Alias (p, _) + | `OpaqueModule p -> + root p end module ModuleType = struct @@ -754,10 +860,22 @@ module Path = struct | `CanonicalType (p, _) -> identifier (p :> t) | `OpaqueModule m -> identifier (m :> t) | `OpaqueModuleType mt -> identifier (mt :> t) + + let is_hidden r = is_resolved_hidden ~weak_canonical_test:false r end module Module = struct type t = Paths_types.Path.module_ + + let rec root : t -> string option = function + | `Resolved r -> Resolved.Module.root r + | `Identifier (id, _) -> ( + match Identifier.root (id :> Identifier.t) with + | Some root -> Some (Identifier.name root) + | None -> None) + | `Root s -> Some s + | `Forward _ -> None + | `Dot (p, _) | `Apply (p, _) -> root p end module ModuleType = struct diff --git a/src/model/paths.mli b/src/model/paths.mli index a4a0f44e1b..d9947933a1 100644 --- a/src/model/paths.mli +++ b/src/model/paths.mli @@ -14,6 +14,9 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +module Ocaml_ident = Ident +module Ocaml_env = Env + (** Identifiers for definitions *) module Identifier : sig @@ -31,6 +34,20 @@ module Identifier : sig val compare : t -> t -> int end + module RootModule : sig + type t = Paths_types.Identifier.root_module + + type t_pv = Paths_types.Identifier.root_module_pv + + val equal : t -> t -> bool + + val hash : t -> int + + val compare : t -> t -> int + + val name : t -> string + end + module Signature : sig type t = Paths_types.Identifier.signature @@ -41,6 +58,8 @@ module Identifier : sig val hash : t -> int val compare : t -> t -> int + + val root : [< t_pv ] id -> RootModule.t end module ClassSignature : sig @@ -91,18 +110,6 @@ module Identifier : sig val compare : t -> t -> int end - module RootModule : sig - type t = Paths_types.Identifier.root_module - - type t_pv = Paths_types.Identifier.root_module_pv - - val equal : t -> t -> bool - - val hash : t -> int - - val compare : t -> t -> int - end - module Module : sig type t = Paths_types.Identifier.module_ @@ -113,6 +120,8 @@ module Identifier : sig val hash : t -> int val compare : t -> t -> int + + val root : t -> RootModule.t end module FunctorParameter : sig @@ -307,6 +316,24 @@ module Identifier : sig val compare : t -> t -> int end + module SourceDir : sig + type t = Paths_types.Identifier.source_dir + type t_pv = Paths_types.Identifier.source_dir_pv + val equal : t -> t -> bool + val hash : t -> int + val compare : t -> t -> int + val name : t -> string + end + + module SourcePage : sig + type t = Paths_types.Identifier.source_page + type t_pv = Paths_types.Identifier.source_page_pv + val equal : t -> t -> bool + val hash : t -> int + val compare : t -> t -> int + val name : t -> string + end + module OdocId : sig type t = Paths_types.Identifier.odoc_id @@ -330,6 +357,8 @@ module Identifier : sig val hash : t -> int val compare : t -> t -> int + + val root : t -> RootModule.t end module ModuleType : sig @@ -377,6 +406,8 @@ module Identifier : sig val name : [< t_pv ] id -> string + val root : [< t_pv ] id -> RootModule.t_pv id option + val compare : t -> t -> int val equal : ([< t_pv ] id as 'a) -> 'a -> bool @@ -418,6 +449,8 @@ module Identifier : sig ContainerPage.t option * PageName.t -> [> `LeafPage of ContainerPage.t option * PageName.t ] id + val source_page : ContainerPage.t * string list -> SourcePage.t + val root : ContainerPage.t option * ModuleName.t -> [> `Root of ContainerPage.t option * ModuleName.t ] id @@ -491,6 +524,8 @@ module rec Path : sig val is_hidden : t -> weak_canonical_test:bool -> bool val identifier : t -> Identifier.Path.Module.t + + val root : t -> string option end module ModuleType : sig @@ -522,10 +557,14 @@ module rec Path : sig type t = Paths_types.Resolved_path.any val identifier : t -> Identifier.t + + val is_hidden : t -> bool end module Module : sig type t = Paths_types.Path.module_ + + val root : t -> string option end module ModuleType : sig diff --git a/src/model/paths_types.ml b/src/model/paths_types.ml index be5d3091dd..0a018de3e0 100644 --- a/src/model/paths_types.ml +++ b/src/model/paths_types.ml @@ -18,6 +18,19 @@ module Identifier = struct and page = page_pv id (** @canonical Odoc_model.Paths.Identifier.Page.t *) + type source_dir_pv = + [ `SourceRoot of container_page | `SourceDir of source_dir * string ] + + and source_dir = source_dir_pv id + + type source_page_pv = [ `SourcePage of source_dir * string ] + (** The second argument is the filename. + + @canonical Odoc_model.Paths.Identifier.SourcePage.t_pv *) + + type source_page = source_page_pv id + (** @canonical Odoc_model.Paths.Identifier.SourcePage.t *) + type odoc_id_pv = [ page_pv | `Root of container_page option * ModuleName.t ] (** @canonical Odoc_model.Paths.Identifier.OdocId.t_pv *) diff --git a/src/model/predefined.ml b/src/model/predefined.ml index 90b2a87a88..7ab6a54c70 100644 --- a/src/model/predefined.ml +++ b/src/model/predefined.ml @@ -23,68 +23,50 @@ let predefined_location = let empty_doc = [] -let nullary_equation = +let mk_equation params = let open TypeDecl.Equation in - let params = [] in - let private_ = false in - let manifest = None in - let constraints = [] in - { params; private_; manifest; constraints } + { params; private_ = false; manifest = None; constraints = [] } +let nullary_equation = mk_equation [] let covariant_equation = - let open TypeDecl in - let open TypeDecl.Equation in - let params = - [ { desc = Var "'a"; variance = Some Pos; injectivity = true } ] - in - let private_ = false in - let manifest = None in - let constraints = [] in - { params; private_; manifest; constraints } - + mk_equation [ { desc = Var "'a"; variance = Some Pos; injectivity = true } ] let invariant_equation = - let open TypeDecl in - let open TypeDecl.Equation in - let params = [ { desc = Var "'a"; variance = None; injectivity = true } ] in - let private_ = false in - let manifest = None in - let constraints = [] in - { params; private_; manifest; constraints } + mk_equation [ { desc = Var "'a"; variance = None; injectivity = true } ] + +let locations = None + +let mk_type ?(doc = empty_doc) ?(eq = nullary_equation) ?repr id = + let locs = locations and canonical = None in + { TypeDecl.id; locs; doc; canonical; equation = eq; representation = repr } + +let mk_exn ~args id = + let locs = locations + and doc = empty_doc + and args = TypeDecl.Constructor.Tuple args + and res = None in + { Exception.id; locs; doc; args; res } + +let mk_constr ?(args = TypeDecl.Constructor.Tuple []) id = + { TypeDecl.Constructor.id; doc = empty_doc; args; res = None } module Mk = Paths.Identifier.Mk let bool_identifier = Mk.core_type "bool" - let int_identifier = Mk.core_type "int" - let char_identifier = Mk.core_type "char" - let bytes_identifier = Mk.core_type "bytes" - let string_identifier = Mk.core_type "string" - let float_identifier = Mk.core_type "float" - let unit_identifier = Mk.core_type "unit" - let exn_identifier = Mk.core_type "exn" - let array_identifier = Mk.core_type "array" - let list_identifier = Mk.core_type "list" - let option_identifier = Mk.core_type "option" - let int32_identifier = Mk.core_type "int32" - let int64_identifier = Mk.core_type "int64" - let nativeint_identifier = Mk.core_type "nativeint" - let lazy_t_identifier = Mk.core_type "lazy_t" - let extension_constructor_identifier = Mk.core_type "extension_constructor" - let floatarray_identifier = Mk.core_type "floatarray" let false_identifier = @@ -109,25 +91,15 @@ let some_identifier = Mk.constructor (option_identifier, ConstructorName.make_std "Some") let match_failure_identifier = Mk.core_exception "Match_failure" - let assert_failure_identifier = Mk.core_exception "Assert_failure" - let invalid_argument_identifier = Mk.core_exception "Invalid_argument" - let failure_identifier = Mk.core_exception "Failure" - let not_found_identifier = Mk.core_exception "Not_found" - let out_of_memory_identifier = Mk.core_exception "Out_of_memory" - let stack_overflow_identifier = Mk.core_exception "Stack_overflow" - let sys_error_identifier = Mk.core_exception "Sys_error" - let end_of_file_identifier = Mk.core_exception "End_of_file" - let division_by_zero_identifier = Mk.core_exception "Division_by_zero" - let sys_blocked_io_identifier = Mk.core_exception "Sys_blocked_io" let undefined_recursive_module_identifier = @@ -181,106 +153,63 @@ let core_constructor_identifier = function | _ -> None let bool_path = `Resolved (`Identifier bool_identifier) - let int_path = `Resolved (`Identifier int_identifier) - let char_path = `Resolved (`Identifier char_identifier) - let bytes_path = `Resolved (`Identifier bytes_identifier) - let string_path = `Resolved (`Identifier string_identifier) - let float_path = `Resolved (`Identifier float_identifier) - let unit_path = `Resolved (`Identifier unit_identifier) - let exn_path = `Resolved (`Identifier exn_identifier) - let array_path = `Resolved (`Identifier array_identifier) - let list_path = `Resolved (`Identifier list_identifier) - let option_path = `Resolved (`Identifier option_identifier) - let int32_path = `Resolved (`Identifier int32_identifier) - let int64_path = `Resolved (`Identifier int64_identifier) - let nativeint_path = `Resolved (`Identifier nativeint_identifier) - let lazy_t_path = `Resolved (`Identifier lazy_t_identifier) let extension_constructor_path = `Resolved (`Identifier extension_constructor_identifier) let _floatarray_path = `Resolved (`Identifier floatarray_identifier) - let bool_reference = `Resolved (`Identifier bool_identifier) - let int_reference = `Resolved (`Identifier int_identifier) - let char_reference = `Resolved (`Identifier char_identifier) - let bytes_reference = `Resolved (`Identifier bytes_identifier) - let string_reference = `Resolved (`Identifier string_identifier) - let float_reference = `Resolved (`Identifier float_identifier) - let unit_reference = `Resolved (`Identifier unit_identifier) - let exn_reference = `Resolved (`Identifier exn_identifier) - let array_reference = `Resolved (`Identifier array_identifier) - let list_reference = `Resolved (`Identifier list_identifier) - let option_reference = `Resolved (`Identifier option_identifier) - let int32_reference = `Resolved (`Identifier int32_identifier) - let int64_reference = `Resolved (`Identifier int64_identifier) - let nativeint_reference = `Resolved (`Identifier nativeint_identifier) - let lazy_t_reference = `Resolved (`Identifier lazy_t_identifier) let extension_constructor_reference = `Resolved (`Identifier extension_constructor_identifier) let _floatarray_reference = `Resolved (`Identifier floatarray_identifier) - let false_reference = `Resolved (`Identifier false_identifier) - let true_reference = `Resolved (`Identifier true_identifier) - let void_reference = `Resolved (`Identifier void_identifier) - let nil_reference = `Resolved (`Identifier nil_identifier) - let cons_reference = `Resolved (`Identifier cons_identifier) - let none_reference = `Resolved (`Identifier none_identifier) - let some_reference = `Resolved (`Identifier some_identifier) - let match_failure_reference = `Resolved (`Identifier match_failure_identifier) - let assert_failure_reference = `Resolved (`Identifier assert_failure_identifier) let invalid_argument_reference = `Resolved (`Identifier invalid_argument_identifier) let failure_reference = `Resolved (`Identifier failure_identifier) - let not_found_reference = `Resolved (`Identifier not_found_identifier) - let out_of_memory_reference = `Resolved (`Identifier out_of_memory_identifier) - let stack_overflow_reference = `Resolved (`Identifier stack_overflow_identifier) - let sys_error_reference = `Resolved (`Identifier sys_error_identifier) - let end_of_file_reference = `Resolved (`Identifier end_of_file_identifier) let division_by_zero_reference = @@ -291,293 +220,51 @@ let sys_blocked_io_reference = `Resolved (`Identifier sys_blocked_io_identifier) let undefined_recursive_module_reference = `Resolved (`Identifier undefined_recursive_module_identifier) -let false_decl = - let open TypeDecl.Constructor in - let doc = empty_doc in - let args = Tuple [] in - let res = None in - { id = false_identifier; doc; args; res } - -let true_decl = - let open TypeDecl.Constructor in - let doc = empty_doc in - let args = Tuple [] in - let res = None in - { id = true_identifier; doc; args; res } - -let void_decl = - let open TypeDecl.Constructor in - let doc = empty_doc in - let args = Tuple [] in - let res = None in - { id = void_identifier; doc; args; res } - -let nil_decl = - let open TypeDecl.Constructor in - let doc = empty_doc in - let args = Tuple [] in - let res = None in - { id = nil_identifier; doc; args; res } +let string_expr = TypeExpr.Constr (string_path, []) +let int_expr = TypeExpr.Constr (int_path, []) + +let false_decl = mk_constr ~args:(Tuple []) false_identifier +let true_decl = mk_constr ~args:(Tuple []) true_identifier +let void_decl = mk_constr ~args:(Tuple []) void_identifier +let nil_decl = mk_constr ~args:(Tuple []) nil_identifier let cons_decl = - let open TypeDecl.Constructor in - let doc = empty_doc in let head = TypeExpr.Var "'a" in let tail = TypeExpr.(Constr (list_path, [ head ])) in - let args = Tuple [ head; tail ] in - let res = None in - { id = cons_identifier; doc; args; res } - -let none_decl = - let open TypeDecl.Constructor in - let doc = empty_doc in - let args = Tuple [] in - let res = None in - { id = none_identifier; doc; args; res } - -let some_decl = - let open TypeDecl.Constructor in - let doc = empty_doc in - let var = TypeExpr.Var "'a" in - let args = Tuple [ var ] in - let res = None in - { id = some_identifier; doc; args; res } - -let int_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = int_identifier in - (* let text = [Raw "The type of integer numbers."] in *) - (* TODO *) - (* let text = [] in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } - -let char_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = char_identifier in - (* let text = [Raw "The type of characters."] in *) - (* let text = [] in *) - (* let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } - -let bytes_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = bytes_identifier in - (* let text = [Raw "The type of (writable) byte sequences."] in *) - (* let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } - -let string_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = string_identifier in - (* let text = [Raw "The type of (read-only) character strings."] in *) - (* let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } - -let float_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = float_identifier in - (* let text = [Raw "The type of floating-point numbers."] in *) - (* let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } + mk_constr ~args:(Tuple [ head; tail ]) cons_identifier +let none_decl = mk_constr ~args:(Tuple []) none_identifier +let some_decl = mk_constr ~args:(Tuple [ TypeExpr.Var "'a" ]) some_identifier + +let int_decl = mk_type int_identifier +let char_decl = mk_type char_identifier +let bytes_decl = mk_type bytes_identifier +let string_decl = mk_type string_identifier +let float_decl = mk_type float_identifier let bool_decl = - let open TypeDecl in - let open Representation in - (* let open Odoc_model.Comment in *) - let id = bool_identifier in - (* let text = [Raw "The type of booleans (truth values)."] in *) - (* let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = Some (Variant [ false_decl; true_decl ]) in - let canonical = None in - { id; doc; canonical; equation; representation } - -let unit_decl = - let open TypeDecl in - let open Representation in - (* let open Odoc_model.Comment in *) - let id = unit_identifier in - (* let text = [Raw "The type of the unit value."] in *) - (* let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = Some (Variant [ void_decl ]) in - let canonical = None in - { id; doc; canonical; equation; representation } - -let exn_decl = - let open TypeDecl in - let open Representation in - (* let open Odoc_model.Comment in *) - let id = exn_identifier in - (* let text = [Raw "The type of exception values."] in *) - (* let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = Some Extensible in - let canonical = None in - { id; doc; canonical; equation; representation } - -let array_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = array_identifier in - (* let text = - [Raw "The type of arrays whose elements have type "; - Code "'a"; - Raw "."] - in *) - (* let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = invariant_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } + mk_type ~repr:(Variant [ false_decl; true_decl ]) bool_identifier +let unit_decl = mk_type ~repr:(Variant [ void_decl ]) unit_identifier +let exn_decl = mk_type ~repr:Extensible exn_identifier +let array_decl = mk_type ~eq:invariant_equation array_identifier let list_decl = - let open TypeDecl in - let open Representation in - (* let open Odoc_model.Comment in *) - let id = list_identifier in - (* let text = - [Raw "The type of lists whose elements have type "; - Code "'a"; - Raw "."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = covariant_equation in - let representation = Some (Variant [ nil_decl; cons_decl ]) in - let canonical = None in - { id; doc; canonical; equation; representation } + mk_type ~eq:covariant_equation + ~repr:(Variant [ nil_decl; cons_decl ]) + list_identifier let option_decl = - let open TypeDecl in - let open Representation in - (* let open Odoc_model.Comment in *) - let id = option_identifier in - (* let text = - [Raw "The type of optional values of type "; - Code "'a"; - Raw "."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = covariant_equation in - let representation = Some (Variant [ none_decl; some_decl ]) in - let canonical = None in - { id; doc; canonical; equation; representation } - -let int32_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = int32_identifier in - (* let text = - [Raw "The type of signed 32-bit integers. See the "; - Reference(Element(Root("Int32", TModule)), None); - Raw " module."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } - -let int64_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = int64_identifier in - (* let text = - [Raw "The type of signed 64-bit integers. See the "; - Reference(Element(Root("Int64", TModule)), None); - Raw " module."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } - -let nativeint_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = nativeint_identifier in - (* let text = - [Raw "The type of signed, platform-native integers (32 bits on \ - 32-bit processors, 64 bits on 64-bit processors). See the "; - Reference(Element(Root("Nativeint", TModule)), None); - Raw " module."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = nullary_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } - -let lazy_t_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = lazy_t_identifier in - (* let text = - [Raw "This type is used to implement the "; - Reference(Element(Root("Lazy", TModule)), None); - Raw " module. It should not be used directly."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = covariant_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } - + mk_type ~eq:covariant_equation + ~repr:(Variant [ none_decl; some_decl ]) + option_identifier + +let int32_decl = mk_type int32_identifier +let int64_decl = mk_type int64_identifier +let nativeint_decl = mk_type nativeint_identifier +let lazy_t_decl = mk_type ~eq:covariant_equation lazy_t_identifier let extension_constructor_decl = - let open TypeDecl in - (* let open Odoc_model.Comment in *) - let id = extension_constructor_identifier in - (* let text = - [Raw "cf. "; - Reference(Element(Root("Obj", TModule)), None); - Raw " module. It should not be used directly."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let equation = covariant_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } + mk_type ~eq:covariant_equation extension_constructor_identifier let floatarray_decl = - let open TypeDecl in - let id = floatarray_identifier in let words ss = ss |> List.rev_map (fun s -> [ `Space; `Word s ]) @@ -600,205 +287,30 @@ let floatarray_decl = ] |> List.map (Location_.at predefined_location) in - let equation = covariant_equation in - let representation = None in - let canonical = None in - { id; doc; canonical; equation; representation } + mk_type ~doc ~eq:covariant_equation floatarray_identifier let match_failure_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = match_failure_identifier in - (* let text = - [Raw "Exception raised when none of the cases of a pattern matching apply. \ - The arguments are the location of the "; - Code "match"; - Raw " keyword in the source code (file name, line number, column number)."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let string_expr = TypeExpr.Constr (string_path, []) in - let int_expr = TypeExpr.Constr (int_path, []) in - let args = - TypeDecl.Constructor.Tuple - [ TypeExpr.Tuple [ string_expr; int_expr; int_expr ] ] - in - let res = None in - { id; doc; args; res } - + mk_exn + ~args:[ TypeExpr.Tuple [ string_expr; int_expr; int_expr ] ] + match_failure_identifier let assert_failure_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = assert_failure_identifier in - (* let text = - [Raw "Exception raised when and assertion fails. \ - The arguments are the location of the "; - Code "assert"; - Raw " keyword in the source code (file name, line number, column number)."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let string_expr = TypeExpr.Constr (string_path, []) in - let int_expr = TypeExpr.Constr (int_path, []) in - let args = - TypeDecl.Constructor.Tuple - [ TypeExpr.Tuple [ string_expr; int_expr; int_expr ] ] - in - let res = None in - { id; doc; args; res } - + mk_exn + ~args:[ TypeExpr.Tuple [ string_expr; int_expr; int_expr ] ] + assert_failure_identifier let invalid_argument_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = invalid_argument_identifier in - (* let text = - [Raw "Exception raised by library functions to signal that the given \ - arguments do not make sense."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [ TypeExpr.Constr (string_path, []) ] in - let res = None in - { id; doc; args; res } - -let failure_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = failure_identifier in - (* let text = - [Raw "Exception raised by library functions to signal that they are \ - undefined on the given arguments."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [ TypeExpr.Constr (string_path, []) ] in - let res = None in - { id; doc; args; res } - -let not_found_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = not_found_identifier in - (* let text = - [Raw "Exception raised by search functions when the desired object \ - could not be found."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [] in - let res = None in - { id; doc; args; res } - -let out_of_memory_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = out_of_memory_identifier in - (* let text = - [Raw "Exception raised by the garbage collector when there is \ - insufficient memory to complete the computation."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [] in - let res = None in - { id; doc; args; res } - -(* TODO: Provide reference to the OCaml manual *) -let stack_overflow_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = stack_overflow_identifier in - (* let text = - [Raw "Exception raised by the bytecode interpreter when the evaluation \ - stack reaches its maximal size. This often indicates infinite or \ - excessively deep recursion in the user's program. (Not fully \ - implemented by the native-code compiler; see section 11.5 of \ - the OCaml manual.)"] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [] in - let res = None in - { id; doc; args; res } - -let sys_error_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = sys_error_identifier in - (* let text = - [Raw "Exception raised by the input/output functions to report an \ - operating system error."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [ TypeExpr.Constr (string_path, []) ] in - let res = None in - { id; doc; args; res } - -let end_of_file_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = end_of_file_identifier in - (* let text = - [Raw "Exception raised by input functions to signal that the end of \ - file has been reached."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [] in - let res = None in - { id; doc; args; res } - -let division_by_zero_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = division_by_zero_identifier in - (* let text = - [Raw "Exception raised by integer division and remainder operations \ - when their second argument is zero."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [] in - let res = None in - { id; doc; args; res } - -let sys_blocked_io_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = sys_blocked_io_identifier in - (* let text = - [Raw "A special case of "; - Reference(Element sys_error_reference, None); - Raw " raised when no I/O is possible on a non-blocking I/O channel."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let args = TypeDecl.Constructor.Tuple [] in - let res = None in - { id; doc; args; res } - -(* TODO: Provide reference to the OCaml manual *) + mk_exn ~args:[ string_expr ] invalid_argument_identifier +let failure_decl = mk_exn ~args:[ string_expr ] failure_identifier +let not_found_decl = mk_exn ~args:[] not_found_identifier +let out_of_memory_decl = mk_exn ~args:[] out_of_memory_identifier +let stack_overflow_decl = mk_exn ~args:[] stack_overflow_identifier +let sys_error_decl = mk_exn ~args:[ string_expr ] sys_error_identifier +let end_of_file_decl = mk_exn ~args:[] end_of_file_identifier +let division_by_zero_decl = mk_exn ~args:[] division_by_zero_identifier +let sys_blocked_io_decl = mk_exn ~args:[] sys_blocked_io_identifier let undefined_recursive_module_decl = - let open Lang.Exception in - (* let open Odoc_model.Comment in *) - let id = undefined_recursive_module_identifier in - (* let text = - [Raw "Exception raised when an ill-founded recursive module definition \ - is evaluated. (See section 7.8 of the OCaml manual.) The arguments \ - are the location of the definition in the source code \ - (file name, line number, column number)."] - in - let doc = Ok {empty_doc with text} in *) - let doc = empty_doc in - let string_expr = TypeExpr.Constr (string_path, []) in - let int_expr = TypeExpr.Constr (int_path, []) in - let args = - TypeDecl.Constructor.Tuple - [ TypeExpr.Tuple [ string_expr; int_expr; int_expr ] ] - in - let res = None in - { id; doc; args; res } + mk_exn + ~args:[ TypeExpr.Tuple [ string_expr; int_expr; int_expr ] ] + undefined_recursive_module_identifier let core_types = [ diff --git a/src/model_desc/lang_desc.ml b/src/model_desc/lang_desc.ml index 17170dfb8f..8f9ea51506 100644 --- a/src/model_desc/lang_desc.ml +++ b/src/model_desc/lang_desc.ml @@ -16,6 +16,18 @@ let inline_status = | `Closed -> C0 "`Closed" | `Inline -> C0 "`Inline") +let locations = + let open Lang.Locations in + Record + [ + F ("source_parent", (fun t -> t.source_parent), sourcepage_identifier); + F ("anchor", (fun t -> t.anchor), Option string); + ] + +let source_info = + let open Lang.Source_info in + Record [ F ("id", (fun t -> t.id), sourcepage_identifier) ] + (** {3 Module} *) let rec module_decl = @@ -34,6 +46,7 @@ and module_t = Record [ F ("id", (fun t -> t.id), identifier); + F ("locs", (fun t -> t.locs), Option locations); F ("doc", (fun t -> t.doc), docs); F ("type_", (fun t -> t.type_), module_decl); F @@ -102,7 +115,7 @@ and moduletype_type_of_desc = | ModPath x -> C ("ModPath", (x :> Paths.Path.t), path) | StructInclude x -> C ("StructInclude", (x :> Paths.Path.t), path)) -and simple_expansion = +and simple_expansion : Lang.ModuleType.simple_expansion T.t = let open Lang.ModuleType in Variant (function @@ -167,6 +180,7 @@ and moduletype_t = Record [ F ("id", (fun t -> t.id), identifier); + F ("locs", (fun t -> t.locs), Option locations); F ("doc", (fun t -> t.doc), docs); F ( "canonical", @@ -356,6 +370,7 @@ and typedecl_t = Record [ F ("id", (fun t -> t.id), identifier); + F ("locs", (fun t -> t.locs), Option locations); F ("doc", (fun t -> t.doc), docs); F ("equation", (fun t -> t.equation), typedecl_equation); F @@ -370,6 +385,7 @@ and extension_constructor = Record [ F ("id", (fun t -> t.id), identifier); + F ("locs", (fun t -> t.locs), Option locations); F ("doc", (fun t -> t.doc), docs); F ("args", (fun t -> t.args), typedecl_constructor_argument); F ("res", (fun t -> t.res), Option typeexpr_t); @@ -393,6 +409,7 @@ and exception_t = Record [ F ("id", (fun t -> t.id), identifier); + F ("locs", (fun t -> t.locs), Option locations); F ("doc", (fun t -> t.doc), docs); F ("args", (fun t -> t.args), typedecl_constructor_argument); F ("res", (fun t -> t.res), Option typeexpr_t); @@ -410,6 +427,7 @@ and value_t = Record [ F ("id", (fun t -> t.id), identifier); + F ("locs", (fun t -> t.locs), Option locations); F ("doc", (fun t -> t.doc), docs); F ("type_", (fun t -> t.type_), typeexpr_t); F ("value", (fun t -> t.value), value_value_t); @@ -433,6 +451,7 @@ and class_t = Record [ F ("id", (fun t -> t.id), identifier); + F ("locs", (fun t -> t.locs), Option locations); F ("doc", (fun t -> t.doc), docs); F ("virtual_", (fun t -> t.virtual_), bool); F ("params", (fun t -> t.params), List typedecl_param); @@ -455,6 +474,7 @@ and classtype_t = Record [ F ("id", (fun t -> t.id), identifier); + F ("locs", (fun t -> t.locs), Option locations); F ("doc", (fun t -> t.doc), docs); F ("virtual_", (fun t -> t.virtual_), bool); F ("params", (fun t -> t.params), List typedecl_param); @@ -670,6 +690,7 @@ and compilation_unit_t = ( "canonical", (fun t -> (t.canonical :> Paths.Path.t option)), Option path ); + F ("sources", (fun t -> t.source_info), Option source_info); ] (** {3 Page} *) @@ -683,3 +704,16 @@ and page_t = F ("content", (fun t -> t.content), docs); F ("digest", (fun t -> t.digest), Digest.t); ] + +and source_tree_page_t = + let open Lang.SourceTree in + Record + [ + F ("name", (fun t -> t.name), identifier); + F ("root", (fun t -> t.root), root); + F ("digest", (fun t -> t.digest), Digest.t); + F + ( "source_children", + (fun t -> t.source_children), + List sourcepage_identifier ); + ] diff --git a/src/model_desc/paths_desc.ml b/src/model_desc/paths_desc.ml index 022504c981..8b23f6d163 100644 --- a/src/model_desc/paths_desc.ml +++ b/src/model_desc/paths_desc.ml @@ -434,6 +434,25 @@ let modulename = Names.modulename let identifier : [< Paths.Identifier.t_pv ] Paths.Identifier.id Type_desc.t = Indirect ((fun n -> (n :> Paths.Identifier.t)), General_paths.identifier) +let rec sourcedir_identifier : Paths.Identifier.SourceDir.t Type_desc.t = + Variant + (fun id -> + match id.iv with + | `SourceDir (parent, name) -> + C ("`SourceDir", (parent, name), Pair (sourcedir_identifier, string)) + | `SourceRoot parent -> + C + ( "`SourceRoot", + (parent :> Paths.Identifier.t), + General_paths.identifier )) + +let sourcepage_identifier : Paths.Identifier.SourcePage.t Type_desc.t = + Indirect + ( (fun id -> + let (`SourcePage (parent, name)) = id.iv in + (parent, name)), + Pair (sourcedir_identifier, string) ) + let resolved_path : [< Paths.Path.Resolved.t ] Type_desc.t = Indirect ((fun n -> (n :> General_paths.rp)), General_paths.resolved_path) diff --git a/src/model_desc/paths_desc.mli b/src/model_desc/paths_desc.mli index 6dca564e62..8bdb184cf6 100644 --- a/src/model_desc/paths_desc.mli +++ b/src/model_desc/paths_desc.mli @@ -6,6 +6,8 @@ val modulename : Odoc_model.Names.ModuleName.t Type_desc.t val identifier : [< Identifier.t_pv ] Odoc_model.Paths.Identifier.id Type_desc.t +val sourcepage_identifier : Odoc_model.Paths.Identifier.SourcePage.t Type_desc.t + val resolved_path : [< Path.Resolved.t ] Type_desc.t val path : [< Path.t ] Type_desc.t diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index 1397acde81..657e607006 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -29,6 +29,24 @@ let convert_directory ?(create = false) () : Fs.Directory.t Arg.conv = let odoc_dir_printer fmt dir = dir_printer fmt (Fs.Directory.to_string dir) in (odoc_dir_parser, odoc_dir_printer) +(** On top of the conversion 'file' that checks that the passed file exists. *) +let convert_fpath = + let parse inp = + match Arg.(conv_parser file) inp with + | Ok s -> Result.Ok (Fs.File.of_string s) + | Error _ as e -> e + and print = Fpath.pp in + Arg.conv (parse, print) + +(** On top of the conversion 'string', split into segs. *) +let convert_source_name = + let parse inp = + match Arg.(conv_parser string) inp with + | Ok s -> Result.Ok (s |> Fs.File.of_string |> Fs.File.segs) + | Error _ as e -> e + and print ppf x = Format.fprintf ppf "%s" (String.concat ~sep:"/" x) in + Arg.conv (parse, print) + let handle_error = function | Result.Ok () -> () | Error (`Cli_error msg) -> @@ -149,7 +167,8 @@ end = struct Fs.File.(set_ext ".odoc" output) let compile hidden directories resolve_fwd_refs dst package_opt - parent_name_opt open_modules children input warnings_options = + parent_name_opt open_modules children input warnings_options + source_parent_file source_name = let open Or_error in let resolver = Resolver.create ~important_digests:(not resolve_fwd_refs) ~directories @@ -167,10 +186,21 @@ end = struct (`Cli_error "Either --package or --parent should be specified, not both") in + let source = + match (source_parent_file, source_name) with + | Some parent, Some name -> Ok (Some (parent, name)) + | Some _, None | None, Some _ -> + Error + (`Cli_error + "--source-parent-file and --source-name must be passed at the \ + same time.") + | None, None -> Ok None + in parent_cli_spec >>= fun parent_cli_spec -> + source >>= fun source -> Fs.Directory.mkdir_p (Fs.File.dirname output); Compile.compile ~resolver ~parent_cli_spec ~hidden ~children ~output - ~warnings_options input + ~warnings_options ~source input let input = let doc = "Input $(i,.cmti), $(i,.cmt), $(i,.cmi) or $(i,.mld) file." in @@ -189,12 +219,32 @@ end = struct let children = let doc = "Specify the $(i,.odoc) file as a child. Can be used multiple times. \ - Only applies to mld files" + Only applies to mld files." in let default = [] in Arg.( value & opt_all string default & info ~docv:"CHILD" ~doc [ "c"; "child" ]) + let source_parent_file = + let doc = + ".odoc file of the parent of the page containing the source code for \ + this compilation unit." + in + Arg.( + value + & opt (some convert_fpath) None + & info [ "source-parent-file" ] ~doc ~docv:"PARENT.odoc") + + let source_name = + let doc = + "The basename of the source file. This is used to place the source file \ + within the source_parent." + in + Arg.( + value + & opt (some convert_source_name) None + & info [ "source-name" ] ~doc ~docv:"NAME") + let cmd = let package_opt = let doc = @@ -220,7 +270,7 @@ end = struct const handle_error $ (const compile $ hidden $ odoc_file_directories $ resolve_fwd_refs $ dst $ package_opt $ parent_opt $ open_modules $ children $ input - $ warnings_options)) + $ warnings_options $ source_parent_file $ source_name)) let info ~docs = let man = @@ -239,6 +289,85 @@ end = struct Term.info "compile" ~docs ~doc ~man end +module Source_tree = struct + let has_src_prefix input = + input |> Fs.File.basename |> Fs.File.to_string + |> Astring.String.is_prefix ~affix:"src-" + + let output_file ~output ~input = + match output with + | Some output -> output + | None -> + let output = + if not (has_src_prefix input) then + let directory = Fs.File.dirname input in + let name = input |> Fs.File.basename |> Fs.File.to_string in + let name = "src-" ^ name in + Fs.File.create ~directory ~name + else input + in + Fs.File.(set_ext ".odoc" output) + + let compile_source_tree directories output parent input warnings_options = + let output = output_file ~output ~input in + let resolver = + Resolver.create ~important_digests:true ~directories ~open_modules:[] + in + Source_tree.compile ~resolver ~parent ~output ~warnings_options input + + let arg_page_output = + let open Or_error in + let parse inp = + match Arg.(conv_parser string) inp with + | Ok s -> + let f = Fs.File.of_string s in + if not (Fs.File.has_ext ".odoc" f) then + Error (`Msg "Output file must have '.odoc' extension.") + else if not (has_src_prefix f) then + Error (`Msg "Output file must be prefixed with 'src-'.") + else Ok f + | Error _ as e -> e + and print = Fpath.pp in + Arg.conv (parse, print) + + let cmd = + let parent = + let doc = "Parent page or subpage." in + Arg.( + required + & opt (some string) None + & info ~docs ~docv:"PARENT" ~doc [ "parent" ]) + in + let dst = + let doc = + "Output file path. Non-existing intermediate directories are created. \ + The basename must start with the prefix 'src-' and extension '.odoc'." + in + Arg.( + value + & opt (some arg_page_output) None + & info ~docs ~docv:"PATH" ~doc [ "o" ]) + in + let input = + let doc = "Input text file containing a line-separated list of paths." in + Arg.( + required & pos 0 (some convert_fpath) None & info ~doc ~docv:"FILE" []) + in + Term.( + const handle_error + $ (const compile_source_tree $ odoc_file_directories $ dst $ parent + $ input $ warnings_options)) + + let info ~docs = + let doc = + "Compile a source tree into a page. Expect a text file containing the \ + relative paths to every source files in the source tree. The paths \ + should be the same as the one passed to $(i,odoc compile \ + --source-name)." + in + Term.info "source-tree" ~docs ~doc +end + module Support_files_command = struct let support_files without_theme output_dir = Support_files.write ~without_theme output_dir @@ -387,11 +516,11 @@ end = struct let process ~docs = Process.(cmd, info ~docs) module Generate = struct - let generate extra _hidden output_dir syntax extra_suffix input_file = + let generate extra _hidden output_dir syntax extra_suffix input_file + warnings_options = let file = Fs.File.of_string input_file in - - Rendering.generate_odoc ~renderer:R.renderer ~syntax ~output:output_dir - ~extra_suffix extra file + Rendering.generate_odoc ~renderer:R.renderer ~warnings_options ~syntax + ~output:output_dir ~extra_suffix extra file let cmd = let syntax = @@ -405,7 +534,7 @@ end = struct Term.( const handle_error $ (const generate $ R.extra_args $ hidden $ dst ~create:true () $ syntax - $ extra_suffix $ input_odocl)) + $ extra_suffix $ input_odocl $ warnings_options)) let info ~docs = let doc = @@ -478,9 +607,7 @@ end = struct end module Odoc_html_args = struct - type args = Odoc_html.Config.t - - let renderer = Html_page.renderer + include Html_page let semantic_uris = let doc = "Generate pretty (semantic) links." in @@ -569,16 +696,29 @@ module Odoc_html_args = struct in Arg.(value & flag & info ~doc [ "as-json" ]) + let source_file = + let doc = + "Source code for the compilation unit. It must have been compiled with \ + --source-parent passed." + in + Arg.( + value + & opt (some convert_fpath) None + & info [ "source" ] ~doc ~docv:"file.ml") + let extra_args = let config semantic_uris closed_details indent theme_uri support_uri flat - as_json = + as_json source_file = let open_details = not closed_details in - Odoc_html.Config.v ~theme_uri ~support_uri ~semantic_uris ~indent ~flat - ~open_details ~as_json () + let html_config = + Odoc_html.Config.v ~theme_uri ~support_uri ~semantic_uris ~indent ~flat + ~open_details ~as_json () + in + { Html_page.html_config; source_file } in Term.( const config $ semantic_uris $ closed_details $ indent $ theme_uri - $ support_uri $ flat $ as_json) + $ support_uri $ flat $ as_json $ source_file) end module Odoc_html = Make_renderer (Odoc_html_args) @@ -857,6 +997,7 @@ let () = Odoc_link.(cmd, info ~docs:section_pipeline); Odoc_html.generate ~docs:section_pipeline; Support_files_command.(cmd, info ~docs:section_pipeline); + Source_tree.(cmd, info ~docs:section_pipeline); Odoc_manpage.generate ~docs:section_generators; Odoc_latex.generate ~docs:section_generators; Odoc_html_url.(cmd, info ~docs:section_support); diff --git a/src/odoc/compile.ml b/src/odoc/compile.ml index 68062e5c6a..99436c283a 100644 --- a/src/odoc/compile.ml +++ b/src/odoc/compile.ml @@ -1,5 +1,7 @@ -open Or_error +open Astring +open Odoc_model open Odoc_model.Names +open Or_error (* * Copyright (c) 2014 Leo White @@ -18,10 +20,8 @@ open Odoc_model.Names *) type parent_spec = - | Explicit of - Odoc_model.Paths.Identifier.ContainerPage.t - * Odoc_model.Paths.Reference.t list - | Package of Odoc_model.Paths.Identifier.ContainerPage.t + | Explicit of Paths.Identifier.ContainerPage.t * Lang.Page.child list + | Package of Paths.Identifier.ContainerPage.t | Noparent type parent_cli_spec = @@ -29,46 +29,74 @@ type parent_cli_spec = | CliPackage of string | CliNoparent -(** Parse parent and child references. May print warnings. *) -let parse_reference f = - let open Odoc_model in - (* This is a command-line error. *) - let warnings_options = { Error.warn_error = true; print_warnings = true } in - Semantics.parse_reference f - |> Error.handle_errors_and_warnings ~warnings_options +let check_is_none msg = function None -> Ok () | Some _ -> Error (`Msg msg) +let check_is_empty msg = function [] -> Ok () | _ :: _ -> Error (`Msg msg) -let parent resolver parent_cli_spec = - let find_parent : - Odoc_model.Paths.Reference.t -> - (Odoc_model.Lang.Page.t, [> `Msg of string ]) Result.result = - fun r -> - match r with - | `Root (p, `TPage) | `Root (p, `TUnknown) -> ( +(** Raises warnings and errors. *) +let lookup_implementation_of_cmti intf_file = + let input_file = Fs.File.set_ext ".cmt" intf_file in + if Fs.File.exists input_file then + let filename = Fs.File.to_string input_file in + Odoc_loader.read_cmt_infos ~filename |> Error.raise_errors_and_warnings + else ( + Error.raise_warning ~non_fatal:true + (Error.filename_only + "No implementation file found for the given interface" + (Fs.File.to_string intf_file)); + None) + +(** Used to disambiguate child references. *) +let is_module_name n = String.length n > 0 && Char.Ascii.is_upper n.[0] + +(** Accepted child references: + + - [page-foo] child is a container or leaf page. + - [module-Foo] child is a module. + - [module-foo], [Foo] child is a module, for backward compatibility. + + Parses [...-"foo"] as [...-foo] for backward compatibility. *) +let parse_parent_child_reference s = + let unquote s = + let len = String.length s in + if String.head s = Some '"' && String.head ~rev:true s = Some '"' && len > 1 + then String.with_range ~first:1 ~len:(len - 2) s + else s + in + match String.cut ~sep:"-" s with + | Some ("page", n) -> Ok (Lang.Page.Page_child (unquote n)) + | Some ("src", n) -> Ok (Source_tree_child (unquote n)) + | Some ("module", n) -> + Ok (Module_child (unquote (String.Ascii.capitalize n))) + | Some (k, _) -> Error (`Msg ("Unrecognized kind: " ^ k)) + | None -> if is_module_name s then Ok (Module_child s) else Ok (Page_child s) + +let resolve_parent_page resolver f = + let find_parent = function + | Lang.Page.Page_child p -> ( match Resolver.lookup_page resolver p with | Some r -> Ok r | None -> Error (`Msg "Couldn't find specified parent page")) - | _ -> Error (`Msg "Expecting page as parent") + | Source_tree_child _ | Module_child _ -> + Error (`Msg "Expecting page as parent") in let extract_parent = function - | { Odoc_model.Paths.Identifier.iv = `Page _; _ } as container -> - Ok container + | { Paths.Identifier.iv = `Page _; _ } as container -> Ok container | _ -> Error (`Msg "Specified parent is not a parent of this file") in + parse_parent_child_reference f >>= fun r -> + find_parent r >>= fun page -> + extract_parent page.name >>= fun parent -> Ok (parent, page.children) + +let parent resolver parent_cli_spec = match parent_cli_spec with | CliParent f -> - parse_reference f >>= fun r -> - find_parent r >>= fun page -> - extract_parent page.name >>= fun parent -> - Ok (Explicit (parent, page.children)) + resolve_parent_page resolver f >>= fun (parent, children) -> + Ok (Explicit (parent, children)) | CliPackage package -> - Ok - (Package - (Odoc_model.Paths.Identifier.Mk.page - (None, PageName.make_std package))) + Ok (Package (Paths.Identifier.Mk.page (None, PageName.make_std package))) | CliNoparent -> Ok Noparent let resolve_imports resolver imports = - let open Odoc_model in List.map (function | Lang.Compilation_unit.Import.Resolved _ as resolved -> resolved @@ -79,24 +107,61 @@ let resolve_imports resolver imports = imports (** Raises warnings and errors. *) -let resolve_and_substitute ~resolver - (parent : Odoc_model.Paths.Identifier.ContainerPage.t option) input_file - read_file = +let resolve_and_substitute ~resolver ~make_root ~source + (parent : Paths.Identifier.ContainerPage.t option) input_file input_type = let filename = Fs.File.to_string input_file in - let unit = - read_file ~parent ~filename |> Odoc_model.Error.raise_errors_and_warnings + (* [impl_shape] is used to lookup locations in the implementation. It is + useless if no source code is given on command line. *) + let should_read_impl_shape = source <> None in + let unit, cmt_infos = + match input_type with + | `Cmti -> + let unit = + Odoc_loader.read_cmti ~make_root ~parent ~filename + |> Error.raise_errors_and_warnings + and cmt_infos = + if should_read_impl_shape then + lookup_implementation_of_cmti input_file + else None + in + (unit, cmt_infos) + | `Cmt -> + Odoc_loader.read_cmt ~make_root ~parent ~filename + |> Error.raise_errors_and_warnings + | `Cmi -> + let unit = + Odoc_loader.read_cmi ~make_root ~parent ~filename + |> Error.raise_errors_and_warnings + in + (unit, None) + in + let impl_shape = + match cmt_infos with Some (shape, _) -> Some shape | None -> None in - if not unit.Odoc_model.Lang.Compilation_unit.interface then + let source_info = + match source with + | Some id -> + let infos = + match cmt_infos with + | Some (_, local_jmp) -> + Odoc_loader.Source_info.of_local_jmp local_jmp + | _ -> [] + in + Some { Lang.Source_info.id; infos } + | None -> None + in + if not unit.Lang.Compilation_unit.interface then Printf.eprintf "WARNING: not processing the \"interface\" file.%s\n%!" (if not (Filename.check_suffix filename "cmt") then "" (* ? *) else Printf.sprintf " Using %S while you should use the .cmti file" filename); (* Resolve imports, used by the [link-deps] command. *) - let unit = { unit with imports = resolve_imports resolver unit.imports } in - let env = Resolver.build_env_for_unit resolver ~linking:false unit in + let unit = + { unit with imports = resolve_imports resolver unit.imports; source_info } + in + let env = Resolver.build_compile_env_for_unit resolver impl_shape unit in let compiled = - Odoc_xref2.Compile.compile ~filename env unit - |> Odoc_model.Error.raise_warnings + Odoc_xref2.Compile.compile ~filename env unit |> Error.raise_warnings in (* [expand unit] fetches [unit] from [env] to get the expansion of local, previously defined, elements. We'd rather it got back the resolved bit so we rebuild an @@ -105,10 +170,10 @@ let resolve_and_substitute ~resolver working on. *) (* let expand_env = Env.build env (`Unit resolved) in*) (* let expanded = Odoc_xref2.Expand.expand (Env.expander expand_env) resolved in *) - compiled + (compiled, impl_shape) let root_of_compilation_unit ~parent_spec ~hidden ~output ~module_name ~digest = - let open Odoc_model.Root in + let open Root in let filename = Filename.chop_extension Fs.File.(to_string @@ basename output) in @@ -116,19 +181,15 @@ let root_of_compilation_unit ~parent_spec ~hidden ~output ~module_name ~digest = let file = Odoc_file.create_unit ~force_hidden:hidden module_name in Ok { - id = - Odoc_model.Paths.Identifier.Mk.root - (parent, ModuleName.make_std module_name); + id = Paths.Identifier.Mk.root (parent, ModuleName.make_std module_name); file; digest; } in - let check_child : Odoc_model.Paths.Reference.t -> bool = - fun c -> - match c with - | `Root (n, `TUnknown) | `Root (n, `TModule) -> - Astring.String.Ascii.(uncapitalize n = uncapitalize filename) - | _ -> false + let check_child = function + | Lang.Page.Module_child n -> + String.Ascii.(uncapitalize n = uncapitalize filename) + | Source_tree_child _ | Page_child _ -> false in match parent_spec with | Noparent -> result None @@ -137,10 +198,26 @@ let root_of_compilation_unit ~parent_spec ~hidden ~output ~module_name ~digest = else Error (`Msg "Specified parent is not a parent of this file") | Package parent -> result (Some parent) +let name_of_output ~prefix output = + let page_dash_root = + Filename.chop_extension Fs.File.(to_string @@ basename output) + in + String.drop ~max:(String.length prefix) page_dash_root + +let page_name_of_output ~is_parent_explicit output = + let root_name = name_of_output ~prefix:"page-" output in + (if is_parent_explicit then + match root_name with + | "index" -> + Format.eprintf + "Warning: Potential name clash - child page named 'index'\n%!" + | _ -> ()); + root_name + let mld ~parent_spec ~output ~children ~warnings_options input = List.fold_left (fun acc child_str -> - match (acc, parse_reference child_str) with + match (acc, parse_parent_child_reference child_str) with | Ok acc, Ok r -> Ok (r :: acc) | Error m, _ -> Error m | _, Error (`Msg m) -> @@ -149,99 +226,115 @@ let mld ~parent_spec ~output ~children ~warnings_options input = (Ok []) children >>= fun children -> let root_name = - let page_dash_root = - Filename.chop_extension Fs.File.(to_string @@ basename output) + let is_parent_explicit = + match parent_spec with Explicit _ -> true | _ -> false in - String.sub page_dash_root (String.length "page-") - (String.length page_dash_root - String.length "page-") + page_name_of_output ~is_parent_explicit output in let input_s = Fs.File.to_string input in let digest = Digest.file input_s in let page_name = PageName.make_std root_name in - let check_child : Odoc_model.Paths.Reference.t -> bool = - fun c -> - match c with - | `Root (n, `TUnknown) | `Root (n, `TPage) -> root_name = n - | _ -> false - in - let _ = - match (parent_spec, root_name) with - | Explicit _, "index" -> - Format.eprintf - "Warning: Potential name clash - child page named 'index'\n%!" - | _ -> () - in - let name = + let check_child = function + | Lang.Page.Page_child n -> root_name = n + | Source_tree_child _ | Module_child _ -> false + in + (if children = [] then + (* No children, this is a leaf page. *) + match parent_spec with + | Explicit (p, _) -> Ok (Paths.Identifier.Mk.leaf_page (Some p, page_name)) + | Package parent -> + Ok (Paths.Identifier.Mk.leaf_page (Some parent, page_name)) + | Noparent -> Ok (Paths.Identifier.Mk.leaf_page (None, page_name)) + else + (* Has children, this is a container page. *) let check parents_children v = if List.exists check_child parents_children then Ok v else Error (`Msg "Specified parent is not a parent of this file") in - let module Mk = Odoc_model.Paths.Identifier.Mk in - match (parent_spec, children) with - | Explicit (p, cs), [] -> check cs @@ Mk.leaf_page (Some p, page_name) - | Explicit (p, cs), _ -> check cs @@ Mk.page (Some p, page_name) - | Package parent, [] -> Ok (Mk.leaf_page (Some parent, page_name)) - | Package parent, _ -> - Ok (Mk.page (Some parent, page_name)) (* This is a bit odd *) - | Noparent, [] -> Ok (Mk.leaf_page (None, page_name)) - | Noparent, _ -> Ok (Mk.page (None, page_name)) - in - name >>= fun name -> + (match parent_spec with + | Explicit (p, cs) -> + check cs @@ Paths.Identifier.Mk.page (Some p, page_name) + | Package parent -> + Ok (Paths.Identifier.Mk.page (Some parent, page_name)) + (* This is a bit odd *) + | Noparent -> Ok (Paths.Identifier.Mk.page (None, page_name))) + >>= fun id -> Ok (id :> Paths.Identifier.Page.t)) + >>= fun name -> let root = - let file = Odoc_model.Root.Odoc_file.create_page root_name in - { - Odoc_model.Root.id = (name :> Odoc_model.Paths.Identifier.OdocId.t); - file; - digest; - } + let file = Root.Odoc_file.create_page root_name in + { Root.id = (name :> Paths.Identifier.OdocId.t); file; digest } in let resolve content = let page = - Odoc_model.Lang.Page. - { name; root; children; content; digest; linked = false } + Lang.Page.{ name; root; children; content; digest; linked = false } in Odoc_file.save_page output ~warnings:[] page; Ok () in Fs.File.read input >>= fun str -> - Odoc_loader.read_string - (name :> Odoc_model.Paths.Identifier.LabelParent.t) - input_s str - |> Odoc_model.Error.handle_errors_and_warnings ~warnings_options + Odoc_loader.read_string (name :> Paths.Identifier.LabelParent.t) input_s str + |> Error.handle_errors_and_warnings ~warnings_options >>= function | `Stop -> resolve [] (* TODO: Error? *) | `Docs content -> resolve content +let handle_file_ext = function + | ".cmti" -> Ok `Cmti + | ".cmt" -> Ok `Cmt + | ".cmi" -> Ok `Cmi + | _ -> + Error (`Msg "Unknown extension, expected one of: cmti, cmt, cmi or mld.") + let compile ~resolver ~parent_cli_spec ~hidden ~children ~output - ~warnings_options input = + ~warnings_options ~source input = parent resolver parent_cli_spec >>= fun parent_spec -> let ext = Fs.File.get_ext input in if ext = ".mld" then - mld ~parent_spec ~output ~warnings_options ~children input + check_is_none "Not expecting source (--source) when compiling pages." source + >>= fun () -> mld ~parent_spec ~output ~warnings_options ~children input else - (match ext with - | ".cmti" -> Ok Odoc_loader.read_cmti - | ".cmt" -> Ok Odoc_loader.read_cmt - | ".cmi" -> Ok Odoc_loader.read_cmi - | _ -> - Error - (`Msg "Unknown extension, expected one of: cmti, cmt, cmi or mld.")) - >>= fun loader -> + check_is_empty "Not expecting children (--child) when compiling modules." + children + >>= fun () -> + (match source with + | Some (parent, name) -> ( + Odoc_file.load parent >>= fun parent -> + let err_not_parent () = + Error (`Msg "Specified source-parent is not a parent of the source.") + in + match parent.Odoc_file.content with + | Odoc_file.Source_tree_content page -> ( + match page.Lang.SourceTree.name with + | { Paths.Identifier.iv = `Page _; _ } as parent_id -> + let name = Paths.Identifier.Mk.source_page (parent_id, name) in + if + List.exists + (Paths.Identifier.SourcePage.equal name) + page.source_children + then Ok (Some name) + else err_not_parent () + | { iv = `LeafPage _; _ } -> err_not_parent ()) + | Unit_content _ | Odoc_file.Page_content _ -> + Error + (`Msg "Specified source-parent should be a page but is a module.") + ) + | None -> Ok None) + >>= fun source -> + handle_file_ext ext >>= fun input_type -> let parent = match parent_spec with - | Noparent -> Ok None - | Explicit (parent, _) -> Ok (Some parent) - | Package parent -> Ok (Some parent) + | Noparent -> None + | Explicit (parent, _) -> Some parent + | Package parent -> Some parent in - parent >>= fun parent -> let make_root = root_of_compilation_unit ~parent_spec ~hidden ~output in let result = - Odoc_model.Error.catch_errors_and_warnings (fun () -> - resolve_and_substitute ~resolver parent input (loader ~make_root)) + Error.catch_errors_and_warnings (fun () -> + resolve_and_substitute ~resolver ~make_root ~source parent input + input_type) in (* Extract warnings to write them into the output file *) - let _, warnings = Odoc_model.Error.unpack_warnings result in - Odoc_model.Error.handle_errors_and_warnings ~warnings_options result - >>= fun unit -> + let _, warnings = Error.unpack_warnings result in + Error.handle_errors_and_warnings ~warnings_options result >>= fun unit -> Odoc_file.save_unit output ~warnings unit; Ok () diff --git a/src/odoc/compile.mli b/src/odoc/compile.mli index 3eaaf6b746..3b3206915a 100644 --- a/src/odoc/compile.mli +++ b/src/odoc/compile.mli @@ -14,6 +14,8 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +open Odoc_model +open Odoc_model.Paths open Or_error type parent_cli_spec = @@ -21,7 +23,16 @@ type parent_cli_spec = | CliPackage of string | CliNoparent -(** Produces .odoc files out of [.cm{i,t,ti}] or .mld files. *) +val name_of_output : prefix:string -> Fs.File.t -> string +(** Compute the name of the page from the output file. Prefix is the prefix to + remove from the filename. *) + +val resolve_parent_page : + Resolver.t -> + string -> + (Identifier.ContainerPage.t * Lang.Page.child list, [> msg ]) result +(** Parse and resolve a parent reference. Returns the identifier of the parent + and its children as a list of reference. *) val compile : resolver:Resolver.t -> @@ -30,5 +41,7 @@ val compile : children:string list -> output:Fs.File.t -> warnings_options:Odoc_model.Error.warnings_options -> + source:(Fpath.t * string list) option -> Fs.File.t -> (unit, [> msg ]) result +(** Produces .odoc files out of [.cm{i,t,ti}] or .mld files. *) diff --git a/src/odoc/depends.ml b/src/odoc/depends.ml index 09f1b8d0a3..100533fa0b 100644 --- a/src/odoc/depends.ml +++ b/src/odoc/depends.ml @@ -66,8 +66,9 @@ end let deps_of_odoc_file ~deps input = Odoc_file.load input >>= fun unit -> match unit.content with - | Page_content _ -> Ok () (* XXX something should certainly be done here *) - | Unit_content unit -> + | Page_content _ | Source_tree_content _ -> + Ok () (* XXX something should certainly be done here *) + | Unit_content (unit, _) -> List.iter unit.Odoc_model.Lang.Compilation_unit.imports ~f:(fun import -> match import with | Odoc_model.Lang.Compilation_unit.Import.Unresolved _ -> () diff --git a/src/odoc/fs.ml b/src/odoc/fs.ml index ed8a5abb6c..a82e0ba0a7 100644 --- a/src/odoc/fs.ml +++ b/src/odoc/fs.ml @@ -42,6 +42,7 @@ module File = struct | Result.Ok psuf -> Fpath.(normalize @@ (directory // psuf)) let to_string = Fpath.to_string + let segs = Fpath.segs let of_string s = match Fpath.of_string s with @@ -91,6 +92,8 @@ module File = struct Result.Error (`Msg err) with Sys_error e -> Result.Error (`Msg e) + let exists file = Sys.file_exists (Fpath.to_string file) + module Table = Hashtbl.Make (struct type nonrec t = t diff --git a/src/odoc/fs.mli b/src/odoc/fs.mli index 88353ee150..af3abcfc24 100644 --- a/src/odoc/fs.mli +++ b/src/odoc/fs.mli @@ -76,7 +76,11 @@ module File : sig val to_string : t -> string + val segs : t -> string list + val read : t -> (string, [> msg ]) result + val exists : t -> bool + module Table : Hashtbl.S with type key = t end diff --git a/src/odoc/html_page.ml b/src/odoc/html_page.ml index 524a62705c..56b5b38630 100644 --- a/src/odoc/html_page.ml +++ b/src/odoc/html_page.ml @@ -14,6 +14,44 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) -let render config page = Odoc_html.Generator.render ~config page +open Odoc_model -let renderer = { Odoc_document.Renderer.name = "html"; render } +type args = { html_config : Odoc_html.Config.t; source_file : Fpath.t option } + +let render { html_config; source_file = _ } page = + Odoc_html.Generator.render ~config:html_config page + +let extra_documents args unit ~syntax = + match (unit.Lang.Compilation_unit.source_info, args.source_file) with + | Some { Lang.Source_info.id; infos }, Some src -> ( + match Fs.File.read src with + | Error (`Msg msg) -> + Error.raise_warning + (Error.filename_only "Couldn't load source file: %s" msg + (Fs.File.to_string src)); + [] + | Ok source_code -> + let infos = infos @ Odoc_loader.Source_info.of_source source_code in + [ + Odoc_document.Renderer.document_of_source ~syntax id infos + source_code; + ]) + | Some { id; _ }, None -> + let filename = Paths.Identifier.SourcePage.name id in + Error.raise_warning + (Error.filename_only + "The --source should be passed when generating documents from \ + compilation units that were compiled with --source-parent and \ + --source-name" + filename); + [] + | None, Some src -> + Error.raise_warning + (Error.filename_only + "--source argument is invalid on compilation unit that were not \ + compiled with --source-parent and --source-name" + (Fs.File.to_string src)); + [] + | None, None -> [] + +let renderer = { Odoc_document.Renderer.name = "html"; render; extra_documents } diff --git a/src/odoc/html_page.mli b/src/odoc/html_page.mli index 0d69969990..77a399d7a8 100644 --- a/src/odoc/html_page.mli +++ b/src/odoc/html_page.mli @@ -16,4 +16,6 @@ open Odoc_document -val renderer : Odoc_html.Config.t Renderer.t +type args = { html_config : Odoc_html.Config.t; source_file : Fpath.t option } + +val renderer : args Renderer.t diff --git a/src/odoc/latex.ml b/src/odoc/latex.ml index 5cbc9f5789..aac321453b 100644 --- a/src/odoc/latex.ml +++ b/src/odoc/latex.ml @@ -5,4 +5,6 @@ type args = { with_children : bool } let render args page = Odoc_latex.Generator.render ~with_children:args.with_children page -let renderer = { Renderer.name = "latex"; render } +let extra_documents _args _unit ~syntax:_ = [] + +let renderer = { Renderer.name = "latex"; render; extra_documents } diff --git a/src/odoc/man_page.ml b/src/odoc/man_page.ml index dd90d36cd7..06a97c0410 100644 --- a/src/odoc/man_page.ml +++ b/src/odoc/man_page.ml @@ -1,5 +1,7 @@ open Odoc_document -let render _ page = [ Odoc_manpage.Generator.render page ] +let render _ page = Odoc_manpage.Generator.render page -let renderer = { Renderer.name = "man"; render } +let extra_documents _args _unit ~syntax:_ = [] + +let renderer = { Renderer.name = "man"; render; extra_documents } diff --git a/src/odoc/odoc_file.ml b/src/odoc/odoc_file.ml index 444cd2079d..a7414a5113 100644 --- a/src/odoc/odoc_file.ml +++ b/src/odoc/odoc_file.ml @@ -17,9 +17,12 @@ open Odoc_model open Or_error +type unit_content = Lang.Compilation_unit.t * Odoc_loader.Lookup_def.t option + type content = | Page_content of Lang.Page.t - | Unit_content of Lang.Compilation_unit.t + | Source_tree_content of Lang.SourceTree.t + | Unit_content of unit_content type t = { content : content; warnings : Odoc_model.Error.t list } @@ -44,9 +47,19 @@ let save_page file ~warnings page = in save_unit file page.Lang.Page.root { content = Page_content page; warnings } -let save_unit file ~warnings m = +let save_source_tree file ~warnings src_page = + let dir = Fs.File.dirname file in + let base = Fs.File.(to_string @@ basename file) in + let file = + if Astring.String.is_prefix ~affix:"src-" base then file + else Fs.File.create ~directory:dir ~name:("src-" ^ base) + in + save_unit file src_page.Lang.SourceTree.root + { content = Source_tree_content src_page; warnings } + +let save_unit file ~warnings (m, s) = save_unit file m.Lang.Compilation_unit.root - { content = Unit_content m; warnings } + { content = Unit_content (m, s); warnings } let load_ file f = let file = Fs.File.to_string file in diff --git a/src/odoc/odoc_file.mli b/src/odoc/odoc_file.mli index 4d65f76335..5c1a704252 100644 --- a/src/odoc/odoc_file.mli +++ b/src/odoc/odoc_file.mli @@ -19,10 +19,13 @@ open Odoc_model open Or_error +type unit_content = Lang.Compilation_unit.t * Odoc_loader.Lookup_def.t option + (** Either a page or a module. *) type content = | Page_content of Lang.Page.t - | Unit_content of Lang.Compilation_unit.t + | Source_tree_content of Lang.SourceTree.t + | Unit_content of unit_content type t = { content : content; warnings : Error.t list } @@ -31,8 +34,12 @@ type t = { content : content; warnings : Error.t list } val save_page : Fs.File.t -> warnings:Error.t list -> Lang.Page.t -> unit (** Save a page. The [page-] prefix is added to the file name if missing. *) -val save_unit : - Fs.File.t -> warnings:Error.t list -> Lang.Compilation_unit.t -> unit +val save_source_tree : + Fs.File.t -> warnings:Error.t list -> Lang.SourceTree.t -> unit +(** Save a source tree page. The [src-] prefix is added to the file name if + missing. *) + +val save_unit : Fs.File.t -> warnings:Error.t list -> unit_content -> unit (** Save a module. *) (** {2 Deserialization} *) diff --git a/src/odoc/odoc_link.ml b/src/odoc/odoc_link.ml index 1d647ed649..503c5d9554 100644 --- a/src/odoc/odoc_link.ml +++ b/src/odoc/odoc_link.ml @@ -4,7 +4,7 @@ let link_page ~resolver ~filename page = let env = Resolver.build_env_for_page resolver page in Odoc_xref2.Link.resolve_page ~filename env page -let link_unit ~resolver ~filename m = +let link_unit ~resolver ~filename m impl_shape = let open Odoc_model in let open Lang.Compilation_unit in let m = @@ -16,7 +16,7 @@ let link_unit ~resolver ~filename m = } else m in - let env = Resolver.build_env_for_unit resolver ~linking:true m in + let env = Resolver.build_link_env_for_unit resolver m impl_shape in Odoc_xref2.Link.link ~filename env m (** [~input_warnings] are the warnings stored in the input file *) @@ -32,15 +32,18 @@ let from_odoc ~resolver ~warnings_options input output = Odoc_file.load input >>= fun unit -> let input_warnings = unit.Odoc_file.warnings in match unit.content with + | Source_tree_content st -> + Odoc_file.save_source_tree output ~warnings:[] st; + Ok (`Source_tree st) | Page_content page -> link_page ~resolver ~filename page |> handle_warnings ~input_warnings ~warnings_options >>= fun (page, warnings) -> Odoc_file.save_page output ~warnings page; Ok (`Page page) - | Unit_content m -> - link_unit ~resolver ~filename m + | Unit_content (m, shape) -> + link_unit ~resolver ~filename m shape |> handle_warnings ~input_warnings ~warnings_options >>= fun (m, warnings) -> - Odoc_file.save_unit output ~warnings m; + Odoc_file.save_unit output ~warnings (m, shape); Ok (`Module m) diff --git a/src/odoc/or_error.ml b/src/odoc/or_error.ml index 6f05572ae7..6eaae71b4c 100644 --- a/src/odoc/or_error.ml +++ b/src/odoc/or_error.ml @@ -3,3 +3,7 @@ type ('a, 'e) result = ('a, 'e) Result.result = Ok of 'a | Error of 'e type msg = [ `Msg of string ] let ( >>= ) r f = match r with Ok v -> f v | Error _ as e -> e + +let rec fold_list f acc = function + | [] -> Ok acc + | hd :: tl -> f acc hd >>= fun acc -> fold_list f acc tl diff --git a/src/odoc/or_error.mli b/src/odoc/or_error.mli index 223cd0c357..67a51c6f7e 100644 --- a/src/odoc/or_error.mli +++ b/src/odoc/or_error.mli @@ -4,3 +4,6 @@ type ('a, 'e) result = ('a, 'e) Result.result = Ok of 'a | Error of 'e type msg = [ `Msg of string ] val ( >>= ) : ('a, 'e) result -> ('a -> ('b, 'e) result) -> ('b, 'e) result + +val fold_list : + ('acc -> 'a -> ('acc, 'e) result) -> 'acc -> 'a list -> ('acc, 'e) result diff --git a/src/odoc/rendering.ml b/src/odoc/rendering.ml index 643c38662b..9ae308620d 100644 --- a/src/odoc/rendering.ml +++ b/src/odoc/rendering.ml @@ -1,22 +1,37 @@ open Odoc_document open Or_error -let document_of_odocl ~syntax input = +let documents_of_unit ~warnings_options ~syntax ~renderer ~extra unit = + Odoc_model.Error.catch_warnings (fun () -> + renderer.Renderer.extra_documents ~syntax extra unit) + |> Odoc_model.Error.handle_warnings ~warnings_options + >>= fun extra_docs -> + let main_doc = + if unit.hidden then [] + else [ Renderer.document_of_compilation_unit ~syntax unit ] + in + Ok (main_doc @ extra_docs) + +let documents_of_odocl ~warnings_options ~renderer ~extra ~syntax input = Odoc_file.load input >>= fun unit -> match unit.content with | Odoc_file.Page_content odoctree -> - Ok (Renderer.document_of_page ~syntax odoctree) - | Unit_content odoctree -> - Ok (Renderer.document_of_compilation_unit ~syntax odoctree) + Ok [ Renderer.document_of_page ~syntax odoctree ] + | Source_tree_content srctree -> + Ok (Renderer.documents_of_source_tree ~syntax srctree) + | Unit_content (odoctree, _) -> + documents_of_unit ~warnings_options ~syntax ~renderer ~extra odoctree -let document_of_input ~resolver ~warnings_options ~syntax input = +let documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax + input = let output = Fs.File.(set_ext ".odocl" input) in Odoc_link.from_odoc ~resolver ~warnings_options input output >>= function - | `Page page -> Ok (Renderer.document_of_page ~syntax page) - | `Module m -> Ok (Renderer.document_of_compilation_unit ~syntax m) + | `Source_tree st -> Ok (Renderer.documents_of_source_tree ~syntax st) + | `Page page -> Ok [ Renderer.document_of_page ~syntax page ] + | `Module m -> documents_of_unit ~warnings_options ~syntax ~renderer ~extra m -let render_document renderer ~output:root_dir ~extra_suffix ~extra odoctree = - let pages = renderer.Renderer.render extra odoctree in +let render_document renderer ~output:root_dir ~extra_suffix ~extra doc = + let pages = renderer.Renderer.render extra doc in Renderer.traverse pages ~f:(fun filename content -> let filename = match extra_suffix with @@ -29,28 +44,37 @@ let render_document renderer ~output:root_dir ~extra_suffix ~extra odoctree = let oc = open_out (Fs.File.to_string filename) in let fmt = Format.formatter_of_out_channel oc in Format.fprintf fmt "%t@?" content; - close_out oc); - Ok () + close_out oc) let render_odoc ~resolver ~warnings_options ~syntax ~renderer ~output extra file = - document_of_input ~resolver ~warnings_options ~syntax file - >>= render_document renderer ~output ~extra_suffix:None ~extra + let extra_suffix = None in + documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax file + >>= fun docs -> + List.iter (render_document renderer ~output ~extra_suffix ~extra) docs; + Ok () -let generate_odoc ~syntax ~renderer ~output ~extra_suffix extra file = - document_of_odocl ~syntax file - >>= render_document renderer ~output ~extra_suffix ~extra +let generate_odoc ~syntax ~warnings_options ~renderer ~output ~extra_suffix + extra file = + documents_of_odocl ~warnings_options ~renderer ~extra ~syntax file + >>= fun docs -> + List.iter (render_document renderer ~output ~extra_suffix ~extra) docs; + Ok () let targets_odoc ~resolver ~warnings_options ~syntax ~renderer ~output:root_dir ~extra odoctree = - let doc = + let docs = if Fpath.get_ext odoctree = ".odoc" then - document_of_input ~resolver ~warnings_options ~syntax odoctree - else document_of_odocl ~syntax odoctree + documents_of_input ~renderer ~extra ~resolver ~warnings_options ~syntax + odoctree + else documents_of_odocl ~warnings_options ~renderer ~extra ~syntax odoctree in - doc >>= fun odoctree -> - let pages = renderer.Renderer.render extra odoctree in - Renderer.traverse pages ~f:(fun filename _content -> - let filename = Fpath.normalize @@ Fs.File.append root_dir filename in - Format.printf "%a\n" Fpath.pp filename); + docs >>= fun docs -> + List.iter + (fun doc -> + let pages = renderer.Renderer.render extra doc in + Renderer.traverse pages ~f:(fun filename _content -> + let filename = Fpath.normalize @@ Fs.File.append root_dir filename in + Format.printf "%a\n" Fpath.pp filename)) + docs; Ok () diff --git a/src/odoc/rendering.mli b/src/odoc/rendering.mli index 0e90d45177..09f18524bc 100644 --- a/src/odoc/rendering.mli +++ b/src/odoc/rendering.mli @@ -13,6 +13,7 @@ val render_odoc : val generate_odoc : syntax:Renderer.syntax -> + warnings_options:Odoc_model.Error.warnings_options -> renderer:'a Renderer.t -> output:Fs.directory -> extra_suffix:string option -> diff --git a/src/odoc/resolver.ml b/src/odoc/resolver.ml index 376a5c5293..01d7b02bdd 100644 --- a/src/odoc/resolver.ml +++ b/src/odoc/resolver.ml @@ -77,7 +77,10 @@ let build_imports_map m = let root_name root = Odoc_model.Root.Odoc_file.name root.Odoc_model.Root.file -let unit_name (Odoc_file.Unit_content { root; _ } | Page_content { root; _ }) = +let unit_name + ( Odoc_file.Unit_content ({ root; _ }, _) + | Page_content { root; _ } + | Source_tree_content { root; _ } ) = root_name root (** TODO: Propagate warnings instead of printing. *) @@ -117,7 +120,7 @@ let rec find_map f = function let lookup_unit_with_digest ap target_name digest = let unit_that_match_digest u = match u with - | Odoc_file.Unit_content m + | Odoc_file.Unit_content (m, _) when Digest.compare m.Odoc_model.Lang.Compilation_unit.digest digest = 0 -> Some m @@ -134,7 +137,9 @@ let lookup_unit_with_digest ap target_name digest = TODO: Correctly propagate warnings instead of printing. *) let lookup_unit_by_name ap target_name = let first_unit u = - match u with Odoc_file.Unit_content m -> Some m | Page_content _ -> None + match u with + | Odoc_file.Unit_content m -> Some m + | Page_content _ | Source_tree_content _ -> None in let rec find_ambiguous tl = match find_map first_unit tl with @@ -150,7 +155,7 @@ let lookup_unit_by_name ap target_name = let ambiguous = m :: ambiguous in let ambiguous = List.map - (fun m -> root_name m.Odoc_model.Lang.Compilation_unit.root) + (fun (m, _) -> root_name m.Odoc_model.Lang.Compilation_unit.root) ambiguous in let warning = @@ -160,22 +165,25 @@ let lookup_unit_by_name ap target_name = ambiguous target_name in prerr_endline (Odoc_model.Error.to_string warning)); - Odoc_xref2.Env.Found m - | None -> Not_found + Some m + | None -> None (** Lookup an unit. First looks into [imports_map] then searches into the paths. *) let lookup_unit ~important_digests ~imports_map ap target_name = + let of_option f = + match f with Some (m, _) -> Odoc_xref2.Env.Found m | None -> Not_found + in match StringMap.find target_name imports_map with | Odoc_model.Lang.Compilation_unit.Import.Unresolved (_, Some digest) -> lookup_unit_with_digest ap target_name digest | Unresolved (_, None) -> if important_digests then Odoc_xref2.Env.Forward_reference - else lookup_unit_by_name ap target_name + else of_option (lookup_unit_by_name ap target_name) | Resolved (root, _) -> lookup_unit_with_digest ap target_name root.digest | exception Not_found -> if important_digests then Odoc_xref2.Env.Not_found - else lookup_unit_by_name ap target_name + else of_option (lookup_unit_by_name ap target_name) (** Lookup a page. @@ -183,7 +191,9 @@ let lookup_unit ~important_digests ~imports_map ap target_name = let lookup_page ap target_name = let target_name = "page-" ^ target_name in let is_page u = - match u with Odoc_file.Page_content p -> Some p | Unit_content _ -> None + match u with + | Odoc_file.Page_content p -> Some p + | Unit_content _ | Source_tree_content _ -> None in let units = load_units_from_name ap target_name in match find_map is_page units with Some (p, _) -> Some p | None -> None @@ -192,7 +202,10 @@ let lookup_page ap target_name = name. *) let add_unit_to_cache u = let target_name = - (match u with Odoc_file.Page_content _ -> "page-" | Unit_content _ -> "") + (match u with + | Odoc_file.Page_content _ -> "page-" + | Unit_content _ -> "" + | Source_tree_content _ -> "page-") ^ unit_name u in Hashtbl.add unit_cache target_name [ u ] @@ -207,29 +220,47 @@ let create ~important_digests ~directories ~open_modules = let ap = Accessible_paths.create ~directories in { important_digests; ap; open_modules } +(** Helpers for creating xref2 env. *) + +open Odoc_xref2 + +let build_compile_env_for_unit + { important_digests; ap; open_modules = open_units } impl_shape m = + add_unit_to_cache (Odoc_file.Unit_content (m, impl_shape)); + let imports_map = build_imports_map m in + let lookup_unit = lookup_unit ~important_digests ~imports_map ap + and lookup_page = lookup_page ap + and lookup_def _ = failwith "Cannot lookup definition" in + let resolver = { Env.open_units; lookup_unit; lookup_page; lookup_def } in + Env.env_of_unit m ~linking:false resolver + (** [important_digests] and [imports_map] only apply to modules. *) -let build ?u { important_digests; ap; open_modules } ~imports_map = - (match u with Some u -> add_unit_to_cache u | None -> ()); +let build ?(imports_map = StringMap.empty) + { important_digests; ap; open_modules = open_units } = + let lookup_def = + Odoc_loader.Lookup_def.lookup_def (fun x -> + match lookup_unit_by_name ap x with + | Some (m, Some shape) -> Some (m, shape) + | _ -> None) + in let lookup_unit = lookup_unit ~important_digests ~imports_map ap and lookup_page = lookup_page ap in - { Odoc_xref2.Env.open_units = open_modules; lookup_unit; lookup_page } + { Env.open_units; lookup_unit; lookup_page; lookup_def } -let build_env_for_unit t ~linking m = +let build_link_env_for_unit t m impl_shape = + add_unit_to_cache (Odoc_file.Unit_content (m, impl_shape)); let imports_map = build_imports_map m in - let resolver = build ~u:(Odoc_file.Unit_content m) t ~imports_map in - Odoc_xref2.Env.env_of_unit m ~linking resolver + let resolver = build ~imports_map t in + Env.env_of_unit m ~linking:true resolver let build_env_for_page t p = - let imports_map = StringMap.empty in - let t = { t with important_digests = false } in - let resolver = build ~u:(Odoc_file.Page_content p) t ~imports_map in - Odoc_xref2.Env.env_of_page p resolver + add_unit_to_cache (Odoc_file.Page_content p); + let resolver = build { t with important_digests = false } in + Env.env_of_page p resolver let build_env_for_reference t = - let imports_map = StringMap.empty in - let t = { t with important_digests = false } in - let resolver = build t ~imports_map in - Odoc_xref2.Env.env_for_reference resolver + let resolver = build { t with important_digests = false } in + Env.env_for_reference resolver let lookup_page t target_name = lookup_page t.ap target_name diff --git a/src/odoc/resolver.mli b/src/odoc/resolver.mli index ea5a0d2fc9..71af842163 100644 --- a/src/odoc/resolver.mli +++ b/src/odoc/resolver.mli @@ -34,11 +34,21 @@ val create : val lookup_page : t -> string -> Odoc_model.Lang.Page.t option -(* val lookup_module *) - -val build_env_for_unit : - t -> linking:bool -> Odoc_model.Lang.Compilation_unit.t -> Odoc_xref2.Env.t -(** Initialize the environment for the given module. *) +(** Helpers for creating xref2 env. *) + +val build_compile_env_for_unit : + t -> + Odoc_loader.Lookup_def.t option -> + Odoc_model.Lang.Compilation_unit.t -> + Odoc_xref2.Env.t +(** Initialize the environment for compiling the given module. *) + +val build_link_env_for_unit : + t -> + Odoc_model.Lang.Compilation_unit.t -> + Odoc_loader.Lookup_def.t option -> + Odoc_xref2.Env.t +(** Initialize the environment for linking the given module. *) val build_env_for_page : t -> Odoc_model.Lang.Page.t -> Odoc_xref2.Env.t (** Initialize the environment for the given page. *) diff --git a/src/odoc/source_tree.ml b/src/odoc/source_tree.ml new file mode 100644 index 0000000000..dbf736ee52 --- /dev/null +++ b/src/odoc/source_tree.ml @@ -0,0 +1,42 @@ +open Astring +open Odoc_model +open Odoc_model.Names +open Or_error +module Id = Paths.Identifier + +let check_is_child_of_parent siblings root_name = + let check_child = function + | Lang.Page.Source_tree_child n -> root_name = n + | Page_child _ | Module_child _ -> false + in + if List.exists check_child siblings then Ok () + else Error (`Msg "Specified parent is not a parent of this file") + +(** Each path is represented as a list of segments. Order is not preserved. *) +let parse_input_file input = + let parse_path p = Fs.File.of_string p |> Fs.File.segs in + let is_sep = function '\n' | '\r' -> true | _ -> false in + Fs.File.read input >>= fun content -> + Ok + ( Digest.file (Fpath.to_string input), + String.fields ~empty:false ~is_sep content |> List.rev_map parse_path ) + +let source_child_id parent segs = Id.Mk.source_page (parent, segs) + +let compile ~resolver ~parent ~output ~warnings_options:_ input = + let root_name = Compile.name_of_output ~prefix:"src-" output in + let page_name = PageName.make_std root_name in + Compile.resolve_parent_page resolver parent >>= fun (parent, siblings) -> + let id = Id.Mk.page (Some parent, page_name) in + check_is_child_of_parent siblings root_name >>= fun () -> + parse_input_file input >>= fun (digest, source_tree) -> + let root = + let file = Root.Odoc_file.create_page root_name in + { Root.id = (id :> Id.OdocId.t); file; digest } + in + let source_children = List.rev_map (source_child_id id) source_tree in + let page = + Lang.SourceTree.{ name = (id :> Id.Page.t); root; source_children; digest } + in + Odoc_file.save_source_tree output ~warnings:[] page; + Ok () diff --git a/src/odoc/source_tree.mli b/src/odoc/source_tree.mli new file mode 100644 index 0000000000..cabcbd8664 --- /dev/null +++ b/src/odoc/source_tree.mli @@ -0,0 +1,11 @@ +open Or_error + +val compile : + resolver:Resolver.t -> + parent:string -> + output:Fs.File.t -> + warnings_options:Odoc_model.Error.warnings_options -> + Fs.File.t -> + (unit, [> msg ]) result +(** Produces a compiled page ([.odoc]) from a file containing a list of paths. + The [resolver] is only used to lookup the parent page. *) diff --git a/src/odoc/url.ml b/src/odoc/url.ml index ecc34a8faf..ee8c52f043 100644 --- a/src/odoc/url.ml +++ b/src/odoc/url.ml @@ -39,7 +39,7 @@ let resolve url_to_string directories reference = print_endline href; Ok ())) -let reference_to_url_html config root_url = +let reference_to_url_html { Html_page.html_config = config; _ } root_url = let url_to_string url = let base = match root_url with diff --git a/src/syntax_highlighter/dune b/src/syntax_highlighter/dune new file mode 100644 index 0000000000..f5186ddba8 --- /dev/null +++ b/src/syntax_highlighter/dune @@ -0,0 +1,7 @@ +(library + (name syntax_highlighter) + (public_name odoc.syntax_highlighter) + (preprocess + (action + (run %{bin:cppo} -V OCAML:%{ocaml_version} %{input-file}))) + (libraries compiler-libs.common)) diff --git a/src/syntax_highlighter/syntax_highlighter.ml b/src/syntax_highlighter/syntax_highlighter.ml new file mode 100644 index 0000000000..83ebebaaa0 --- /dev/null +++ b/src/syntax_highlighter/syntax_highlighter.ml @@ -0,0 +1,168 @@ +type token = Parser.token + +let tag_of_token (tok : Parser.token) = + match tok with + | AMPERAMPER -> "AMPERAMPER" + | AMPERSAND -> "AMPERSAND" + | AND -> "AND" + | AS -> "AS" + | ASSERT -> "ASSERT" + | BACKQUOTE -> "BACKQUOTE" + | BANG -> "BANG" + | BAR -> "BAR" + | BARBAR -> "BARBAR" + | BARRBRACKET -> "BARRBRACKET" + | BEGIN -> "BEGIN" + | CHAR _ -> "CHAR" + | CLASS -> "CLASS" + | COLON -> "COLON" + | COLONCOLON -> "COLONCOLON" + | COLONEQUAL -> "COLONEQUAL" + | COLONGREATER -> "COLONGREATER" + | COMMA -> "COMMA" + | COMMENT _ -> "COMMENT" + | CONSTRAINT -> "CONSTRAINT" + | DO -> "DO" + | DOCSTRING _ -> "DOCSTRING" + | DONE -> "DONE" + | DOT -> "DOT" + | DOTDOT -> "DOTDOT" + | DOWNTO -> "DOWNTO" + | ELSE -> "ELSE" + | END -> "END" + | EOF -> "EOF" + | EOL -> "EOL" + | EQUAL -> "EQUAL" + | EXCEPTION -> "EXCEPTION" + | EXTERNAL -> "EXTERNAL" + | FALSE -> "FALSE" + | FLOAT _ -> "FLOAT" + | FOR -> "FOR" + | FUN -> "FUN" + | FUNCTION -> "FUNCTION" + | FUNCTOR -> "FUNCTOR" + | GREATER -> "GREATER" + | GREATERRBRACE -> "GREATERRBRACE" + | GREATERRBRACKET -> "GREATERRBRACKET" + | IF -> "IF" + | IN -> "IN" + | INCLUDE -> "INCLUDE" + | INFIXOP0 _ -> "INFIXOP0" + | INFIXOP1 _ -> "INFIXOP1" + | INFIXOP2 _ -> "INFIXOP2" + | INFIXOP3 _ -> "INFIXOP3" + | INFIXOP4 _ -> "INFIXOP4" + | INHERIT -> "INHERIT" + | INITIALIZER -> "INITIALIZER" + | INT _ -> "INT" + | LABEL _ -> "LABEL" + | LAZY -> "LAZY" + | LBRACE -> "LBRACE" + | LBRACELESS -> "LBRACELESS" + | LBRACKET -> "LBRACKET" + | LBRACKETAT -> "LBRACKETAT" + | LBRACKETATAT -> "LBRACKETATAT" + | LBRACKETATATAT -> "LBRACKETATATAT" + | LBRACKETBAR -> "LBRACKETBAR" + | LBRACKETGREATER -> "LBRACKETGREATER" + | LBRACKETLESS -> "LBRACKETLESS" + | LBRACKETPERCENT -> "LBRACKETPERCENT" + | LBRACKETPERCENTPERCENT -> "LBRACKETPERCENTPERCENT" + | LESS -> "LESS" + | LESSMINUS -> "LESSMINUS" + | LET -> "LET" + | LIDENT "failwith" -> "failwith" + | LIDENT _ -> "LIDENT" + | LPAREN -> "LPAREN" + | MATCH -> "MATCH" + | METHOD -> "METHOD" + | MINUS -> "MINUS" + | MINUSDOT -> "MINUSDOT" + | MINUSGREATER -> "MINUSGREATER" + | MODULE -> "MODULE" + | MUTABLE -> "MUTABLE" + | NEW -> "NEW" + | NONREC -> "NONREC" + | OBJECT -> "OBJECT" + | OF -> "OF" + | OPEN -> "OPEN" + | OPTLABEL _ -> "OPTLABEL" + | OR -> "OR" + | PERCENT -> "PERCENT" + | PLUS -> "PLUS" + | PLUSDOT -> "PLUSDOT" + | PLUSEQ -> "PLUSEQ" + | PREFIXOP _ -> "PREFIXOP" + | PRIVATE -> "PRIVATE" + | QUESTION -> "QUESTION" + | QUOTE -> "QUOTE" + | RBRACE -> "RBRACE" + | RBRACKET -> "RBRACKET" + | REC -> "REC" + | RPAREN -> "RPAREN" + | SEMI -> "SEMI" + | SEMISEMI -> "SEMISEMI" + | SIG -> "SIG" + | STAR -> "STAR" + | STRING _ -> "STRING" + | STRUCT -> "STRUCT" + | THEN -> "THEN" + | TILDE -> "TILDE" + | TO -> "TO" + | TRUE -> "TRUE" + | TRY -> "TRY" + | TYPE -> "TYPE" + | UIDENT _ -> "UIDENT" + | UNDERSCORE -> "UNDERSCORE" + | VAL -> "VAL" + | VIRTUAL -> "VIRTUAL" + | WHEN -> "WHEN" + | WHILE -> "WHILE" + | WITH -> "WITH" +(* Removed *) +#if OCAML_VERSION <= (4,2,3) + | INT32 _ -> "INT32" + | INT64 _ -> "INT64" + | NATIVEINT _ -> "NATIVEINT" +#endif +#if OCAML_VERSION <= (4,3,0) + | SHARP -> "SHARP" + | SHARPOP _ -> "SHARPOP" +#endif +(* Added *) +#if OCAML_VERSION >= (4,4,0) + | HASH -> "HASH" + | HASHOP _ -> "HASHOP" +#endif +#if OCAML_VERSION >= (4,6,0) + | DOTOP _ -> "DOTOP" +#endif +#if OCAML_VERSION >= (4,11,0) + | QUOTED_STRING_EXPR _ -> "QUOTED_STRING_EXPR" + | QUOTED_STRING_ITEM _ -> "QUOTED_STRING_ITEM" +#endif +#if OCAML_VERSION >= (4,8,0) + | ANDOP _ -> "ANDOP" + | LETOP _ -> "LETOP" +#endif + +let syntax_highlighting_locs src = + let lexbuf = Lexing.from_string +#if OCAML_VERSION >= (4,8,0) + ~with_positions:true +#endif + src in + let rec collect lexbuf = + let tok = Lexer.token_with_comments lexbuf in + let loc_start, loc_end = (lexbuf.lex_start_p, lexbuf.lex_curr_p) in + let tag = tag_of_token tok in + match tok with + | EOF -> [] + | COMMENT (_, loc) -> + (tag, (loc.loc_start.pos_cnum, loc.loc_end.pos_cnum)) :: collect lexbuf + | DOCSTRING doc -> + let loc = Docstrings.docstring_loc doc in + (tag, (loc.loc_start.pos_cnum, loc.loc_end.pos_cnum)) :: collect lexbuf + | _ -> (tag, (loc_start.pos_cnum, loc_end.pos_cnum)) :: collect lexbuf + in + collect lexbuf diff --git a/src/xref2/compile.ml b/src/xref2/compile.ml index 68cbb8049b..0a1d1530bc 100644 --- a/src/xref2/compile.ml +++ b/src/xref2/compile.ml @@ -369,8 +369,8 @@ and include_ : Env.t -> Include.t -> Include.t * Env.t = let open Utils.ResultMonad in match decl with | Alias p -> - Tools.expansion_of_module_path env ~strengthen:true p - >>= Tools.assert_not_functor + Tools.expansion_of_module_path env ~strengthen:true p >>= fun exp -> + Tools.assert_not_functor exp | ModuleType mty -> Tools.signature_of_u_module_type_expr ~mark_substituted:false env mty with diff --git a/src/xref2/component.ml b/src/xref2/component.ml index 69e83900b1..2b639d06b0 100644 --- a/src/xref2/component.ml +++ b/src/xref2/component.ml @@ -76,6 +76,7 @@ module rec Module : sig | ModuleType of ModuleType.expr type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; type_ : decl; canonical : Odoc_model.Paths.Path.Module.t option; @@ -147,6 +148,7 @@ and Extension : sig module Constructor : sig type t = { name : string; + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; args : TypeDecl.Constructor.argument; res : TypeExpr.t option; @@ -165,6 +167,7 @@ end = and Exception : sig type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; args : TypeDecl.Constructor.argument; res : TypeExpr.t option; @@ -228,6 +231,7 @@ and ModuleType : sig | TypeOf of typeof_t type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; canonical : Odoc_model.Paths.Path.ModuleType.t option; expr : expr option; @@ -275,6 +279,7 @@ and TypeDecl : sig end type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; canonical : Odoc_model.Paths.Path.Type.t option; equation : Equation.t; @@ -286,7 +291,12 @@ end = and Value : sig type value = Odoc_model.Lang.Value.value - type t = { doc : CComment.docs; type_ : TypeExpr.t; value : value } + type t = { + locs : Odoc_model.Lang.Locations.t option; + doc : CComment.docs; + type_ : TypeExpr.t; + value : value; + } end = Value @@ -353,6 +363,7 @@ and Class : sig | Arrow of TypeExpr.label option * TypeExpr.t * decl type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; virtual_ : bool; params : TypeDecl.param list; @@ -368,6 +379,7 @@ and ClassType : sig | Signature of ClassSignature.t type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; virtual_ : bool; params : TypeDecl.param list; @@ -1864,7 +1876,8 @@ module Of_Lang = struct let rec type_decl ident_map ty = let open Odoc_model.Lang.TypeDecl in { - TypeDecl.doc = docs ident_map ty.doc; + TypeDecl.locs = ty.locs; + doc = docs ident_map ty.doc; canonical = ty.canonical; equation = type_equation ident_map ty.equation; representation = @@ -1989,10 +2002,10 @@ module Of_Lang = struct and module_decl ident_map m = match m with - | Odoc_model.Lang.Module.Alias (p, e) -> + | Lang.Module.Alias (p, e) -> Module.Alias (module_path ident_map p, option simple_expansion ident_map e) - | Odoc_model.Lang.Module.ModuleType s -> + | Lang.Module.ModuleType s -> Module.ModuleType (module_type_expr ident_map s) and include_decl ident_map m = @@ -2028,7 +2041,13 @@ module Of_Lang = struct and module_ ident_map m = let type_ = module_decl ident_map m.Odoc_model.Lang.Module.type_ in let canonical = m.Odoc_model.Lang.Module.canonical in - { Module.doc = docs ident_map m.doc; type_; canonical; hidden = m.hidden } + { + Module.locs = m.locs; + doc = docs ident_map m.doc; + type_; + canonical; + hidden = m.hidden; + } and with_module_type_substitution ident_map m = let open Odoc_model.Lang.ModuleType in @@ -2078,6 +2097,7 @@ module Of_Lang = struct let res = Opt.map (type_expression ident_map) c.res in { Extension.Constructor.name = Paths.Identifier.name c.id; + locs = c.locs; doc = docs ident_map c.doc; args; res; @@ -2087,7 +2107,7 @@ module Of_Lang = struct let open Odoc_model.Lang.Exception in let args = type_decl_constructor_argument ident_map e.args in let res = Opt.map (type_expression ident_map) e.res in - { Exception.doc = docs ident_map e.doc; args; res } + { Exception.locs = e.locs; doc = docs ident_map e.doc; args; res } and u_module_type_expr ident_map m = let open Odoc_model in @@ -2169,11 +2189,16 @@ module Of_Lang = struct let expr = Opt.map (module_type_expr ident_map) m.Odoc_model.Lang.ModuleType.expr in - { ModuleType.doc = docs ident_map m.doc; canonical = m.canonical; expr } + { + ModuleType.locs = m.locs; + doc = docs ident_map m.doc; + canonical = m.canonical; + expr; + } and value ident_map v = let type_ = type_expression ident_map v.Lang.Value.type_ in - { Value.type_; doc = docs ident_map v.doc; value = v.value } + { Value.type_; doc = docs ident_map v.doc; value = v.value; locs = v.locs } and include_ ident_map i = let open Odoc_model.Lang.Include in @@ -2193,7 +2218,8 @@ module Of_Lang = struct let open Odoc_model.Lang.Class in let expansion = Opt.map (class_signature ident_map) c.expansion in { - Class.doc = docs ident_map c.doc; + Class.locs = c.locs; + doc = docs ident_map c.doc; virtual_ = c.virtual_; params = c.params; type_ = class_decl ident_map c.type_; @@ -2219,7 +2245,8 @@ module Of_Lang = struct let open Odoc_model.Lang.ClassType in let expansion = Opt.map (class_signature ident_map) t.expansion in { - ClassType.doc = docs ident_map t.doc; + ClassType.locs = t.locs; + doc = docs ident_map t.doc; virtual_ = t.virtual_; params = t.params; expr = class_type_expr ident_map t.expr; @@ -2296,11 +2323,11 @@ module Of_Lang = struct and module_of_module_substitution ident_map (t : Odoc_model.Lang.ModuleSubstitution.t) = let manifest = module_path ident_map t.manifest in - let canonical = None in { - Module.doc = docs ident_map t.doc; + Module.locs = None; + doc = docs ident_map t.doc; type_ = Alias (manifest, None); - canonical; + canonical = None; hidden = false; } @@ -2405,7 +2432,8 @@ end let module_of_functor_argument (arg : FunctorParameter.parameter) = { - Module.doc = []; + Module.locs = None; + doc = []; type_ = ModuleType arg.expr; canonical = None; hidden = false; diff --git a/src/xref2/component.mli b/src/xref2/component.mli index 1a638a1905..cff8b5fd28 100644 --- a/src/xref2/component.mli +++ b/src/xref2/component.mli @@ -66,6 +66,7 @@ module rec Module : sig | ModuleType of ModuleType.expr type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; type_ : decl; canonical : Odoc_model.Paths.Path.Module.t option; @@ -133,6 +134,7 @@ and Extension : sig module Constructor : sig type t = { name : string; + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; args : TypeDecl.Constructor.argument; res : TypeExpr.t option; @@ -150,6 +152,7 @@ end and Exception : sig type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; args : TypeDecl.Constructor.argument; res : TypeExpr.t option; @@ -211,6 +214,7 @@ and ModuleType : sig | TypeOf of typeof_t type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; canonical : Odoc_model.Paths.Path.ModuleType.t option; expr : expr option; @@ -257,6 +261,7 @@ and TypeDecl : sig end type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; canonical : Odoc_model.Paths.Path.Type.t option; equation : Equation.t; @@ -320,7 +325,12 @@ end and Value : sig type value = Odoc_model.Lang.Value.value - type t = { doc : CComment.docs; type_ : TypeExpr.t; value : value } + type t = { + locs : Odoc_model.Lang.Locations.t option; + doc : CComment.docs; + type_ : TypeExpr.t; + value : value; + } end and Class : sig @@ -329,6 +339,7 @@ and Class : sig | Arrow of TypeExpr.label option * TypeExpr.t * decl type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; virtual_ : bool; params : TypeDecl.param list; @@ -343,6 +354,7 @@ and ClassType : sig | Signature of ClassSignature.t type t = { + locs : Odoc_model.Lang.Locations.t option; doc : CComment.docs; virtual_ : bool; params : TypeDecl.param list; diff --git a/src/xref2/dune b/src/xref2/dune index 9abad17f33..5294d0d380 100644 --- a/src/xref2/dune +++ b/src/xref2/dune @@ -1,7 +1,7 @@ (library (name odoc_xref2) (public_name odoc.xref2) - (libraries compiler-libs.common odoc_model unix)) + (libraries odoc_model)) (rule (alias runmdx) diff --git a/src/xref2/env.ml b/src/xref2/env.ml index d4f45b5a29..6a277a36ae 100644 --- a/src/xref2/env.ml +++ b/src/xref2/env.ml @@ -5,20 +5,20 @@ open Odoc_model.Paths type lookup_unit_result = | Forward_reference - | Found of Odoc_model.Lang.Compilation_unit.t + | Found of Lang.Compilation_unit.t | Not_found -type lookup_page_result = Odoc_model.Lang.Page.t option +type lookup_page_result = Lang.Page.t option type root = - | Resolved of - (Root.t * Odoc_model.Paths.Identifier.Module.t * Component.Module.t) + | Resolved of (Odoc_model.Root.t * Identifier.Module.t * Component.Module.t) | Forward type resolver = { open_units : string list; lookup_unit : string -> lookup_unit_result; lookup_page : string -> lookup_page_result; + lookup_def : Identifier.t -> Lang.Locations.t option; } let unique_id = @@ -28,10 +28,10 @@ let unique_id = !i type lookup_type = - | Module of Odoc_model.Paths.Identifier.Path.Module.t - | ModuleType of Odoc_model.Paths.Identifier.Path.ModuleType.t + | Module of Paths.Identifier.Path.Module.t + | ModuleType of Paths.Identifier.Path.ModuleType.t | RootModule of string * [ `Forward | `Resolved of Digest.t ] option - | ModuleByName of string * Odoc_model.Paths.Identifier.Path.Module.t + | ModuleByName of string * Paths.Identifier.Path.Module.t | FragmentRoot of int let pp_lookup_type fmt = @@ -69,7 +69,7 @@ end) type recorder = { mutable lookups : LookupTypeSet.t } -module Maps = Odoc_model.Paths.Identifier.Maps +module Maps = Paths.Identifier.Maps module StringMap = Map.Make (String) (** Used only to handle shadowing, see {!Elements}. *) @@ -153,8 +153,8 @@ type 'a amb_err = [ `Ambiguous of 'a * 'a list ] type t = { linking : bool; - (* True if this is a linking environment - if not, - we only put in modules, module types, types, classes and class types *) + (* True if this is a linking environment - if not, we only put in modules, + module types, types, classes and class types *) id : int; elts : ElementsByName.t; (** Elements mapped by their name. Queried with {!find_by_name}. *) @@ -259,23 +259,23 @@ let add_label identifier heading env = ids = ElementsById.add identifier comp env.ids; } -let add_docs (docs : Odoc_model.Comment.docs) env = +let add_docs (docs : Comment.docs) env = assert env.linking; List.fold_left (fun env -> function - | { Odoc_model.Location_.value = `Heading (attrs, id, text); location } -> + | { Location_.value = `Heading (attrs, id, text); location } -> let label = Ident.Of_Identifier.label id in add_label id { Component.Label.attrs; label; text; location } env | _ -> env) env docs -let add_comment (com : Odoc_model.Comment.docs_or_stop) env = +let add_comment (com : Comment.docs_or_stop) env = match com with `Docs doc -> add_docs doc env | `Stop -> env let add_cdocs p (docs : Component.CComment.docs) env = List.fold_left (fun env element -> - match element.Odoc_model.Location_.value with + match element.Location_.value with | `Heading h -> let (`LLabel (name, _)) = h.Component.Label.label in let label = @@ -301,7 +301,7 @@ let add_type identifier t env = and add_field env (field : TypeDecl.Field.t) = let ident = Paths.Identifier.Mk.field - ( (identifier :> Odoc_model.Paths.Identifier.Parent.t), + ( (identifier :> Paths.Identifier.Parent.t), FieldName.make_std field.name ) in add_to_elts Kind_Field ident (`Field (ident, field)) env @@ -356,14 +356,21 @@ let add_extension_constructor identifier add_to_elts Kind_Extension identifier (`Extension (identifier, ec)) env |> add_cdocs identifier ec.doc -let module_of_unit : Odoc_model.Lang.Compilation_unit.t -> Component.Module.t = +let module_of_unit : Lang.Compilation_unit.t -> Component.Module.t = fun unit -> + let id = (unit.id :> Paths.Identifier.Module.t) in + let locs = + match unit.source_info with + | Some src -> Some { Lang.Locations.source_parent = src.id; anchor = None } + | None -> None + in match unit.content with | Module s -> let m = - Odoc_model.Lang.Module. + Lang.Module. { - id = (unit.id :> Odoc_model.Paths.Identifier.Module.t); + id; + locs; doc = []; type_ = ModuleType (Signature s); canonical = unit.canonical; @@ -374,9 +381,10 @@ let module_of_unit : Odoc_model.Lang.Compilation_unit.t -> Component.Module.t = ty | Pack _p -> let m = - Odoc_model.Lang.Module. + Lang.Module. { - id = (unit.id :> Odoc_model.Paths.Identifier.Module.t); + id; + locs; doc = []; type_ = ModuleType (Signature { items = []; compiled = true; doc = [] }); @@ -416,9 +424,16 @@ let lookup_root_module name env = | None, _ -> ()); result +let lookup_def id env = + let id = (id :> Paths.Identifier.Any.t) in + match env.resolver with Some r -> r.lookup_def id | None -> None + let lookup_page name env = match env.resolver with None -> None | Some r -> r.lookup_page name +let lookup_unit name env = + match env.resolver with None -> None | Some r -> Some (r.lookup_unit name) + type 'a scope = { filter : Component.Element.any -> ([< Component.Element.any ] as 'a) option; check : (t -> ([< Component.Element.any ] as 'a) -> 'a amb_err option) option; @@ -593,31 +608,25 @@ let lookup_fragment_root env = result | None -> None -let add_functor_parameter : Odoc_model.Lang.FunctorParameter.t -> t -> t = +let mk_functor_parameter module_type = + let type_ = Component.Module.ModuleType module_type in + Component.Module. + { locs = None; doc = []; type_; canonical = None; hidden = false } + +let add_functor_parameter : Lang.FunctorParameter.t -> t -> t = fun p t -> match p with | Unit -> t | Named n -> + let id = (n.id :> Paths.Identifier.Path.Module.t) in let m = - Component.Module. - { - doc = []; - type_ = - ModuleType Component.Of_Lang.(module_type_expr (empty ()) n.expr); - canonical = None; - hidden = false; - } + let open Component.Of_Lang in + mk_functor_parameter (module_type_expr (empty ()) n.expr) in - add_module - (n.id :> Paths.Identifier.Path.Module.t) - (Component.Delayed.put_val m) - [] t + add_module id (Component.Delayed.put_val m) [] t let add_functor_args' : - Odoc_model.Paths.Identifier.Signature.t -> - Component.ModuleType.expr -> - t -> - t = + Paths.Identifier.Signature.t -> Component.ModuleType.expr -> t -> t = let open Component in fun id expr env -> let rec find_args parent mty = @@ -628,20 +637,16 @@ let add_functor_args' : ( parent, Ident.Name.typed_functor_parameter arg.Component.FunctorParameter.id ), - { - Component.Module.doc = []; - type_ = ModuleType arg.expr; - canonical = None; - hidden = false; - } ) + mk_functor_parameter arg.expr ) :: find_args (Paths.Identifier.Mk.result parent) res | ModuleType.Functor (Unit, res) -> find_args (Paths.Identifier.Mk.result parent) res | _ -> [] in - (* We substituted back the parameters as identifiers to maintain the invariant that - components in the environment are 'self-contained' - that is, they only contain - local idents for things that are declared within themselves *) + (* We substituted back the parameters as identifiers to maintain the + invariant that components in the environment are 'self-contained' - that + is, they only contain local idents for things that are declared within + themselves *) let fold_fn (env, subst) (ident, identifier, m) = let ident, identifier = ((ident, identifier) :> Ident.path_module * Identifier.Path.Module.t) @@ -662,31 +667,30 @@ let add_module_functor_args m id env = match m.Component.Module.type_ with | Alias _ -> env | ModuleType expr -> - add_functor_args' (id :> Odoc_model.Paths.Identifier.Signature.t) expr env + add_functor_args' (id :> Paths.Identifier.Signature.t) expr env let add_module_type_functor_args mt id env = match mt.Component.ModuleType.expr with | None -> env - | Some expr -> - add_functor_args' (id :> Odoc_model.Paths.Identifier.Signature.t) expr env + | Some expr -> add_functor_args' (id :> Paths.Identifier.Signature.t) expr env -let open_class_signature : Odoc_model.Lang.ClassSignature.t -> t -> t = +let open_class_signature : Lang.ClassSignature.t -> t -> t = let open Component in let open Of_Lang in fun s env -> List.fold_left (fun env orig -> match orig with - | Odoc_model.Lang.ClassSignature.Method m -> + | Lang.ClassSignature.Method m -> let ty = method_ (empty ()) m in - add_method m.Odoc_model.Lang.Method.id ty env + add_method m.Lang.Method.id ty env | _ -> env) env s.items -let rec open_signature : Odoc_model.Lang.Signature.t -> t -> t = +let rec open_signature : Lang.Signature.t -> t -> t = let open Component in let open Of_Lang in - let module L = Odoc_model.Lang in + let module L = Lang in fun s e -> let ident_map = empty () in List.fold_left @@ -746,15 +750,13 @@ let open_type_substitution : Odoc_model.Lang.TypeDecl.t -> t -> t = fun t env -> let open Component in let open Of_Lang in - let module L = Odoc_model.Lang in let ty = type_decl (empty ()) t in - add_type t.L.TypeDecl.id ty env + add_type t.Lang.TypeDecl.id ty env let open_module_substitution : Odoc_model.Lang.ModuleSubstitution.t -> t -> t = fun m env -> let open Component in let open Of_Lang in - let module L = Odoc_model.Lang in let _id = Ident.Of_Identifier.module_ m.id in let doc = docs (empty ()) m.doc in let ty = @@ -767,17 +769,21 @@ let open_module_substitution : Odoc_model.Lang.ModuleSubstitution.t -> t -> t = in add_module (m.id :> Identifier.Path.Module.t) ty doc env -let open_module_type_substitution : - Odoc_model.Lang.ModuleTypeSubstitution.t -> t -> t = +let open_module_type_substitution : Lang.ModuleTypeSubstitution.t -> t -> t = fun t env -> let open Component in let open Of_Lang in - let module L = Odoc_model.Lang in let ty = module_type (empty ()) - { id = t.id; doc = t.doc; expr = Some t.manifest; canonical = None } + { + id = t.id; + locs = None; + doc = t.doc; + expr = Some t.manifest; + canonical = None; + } in - add_module_type t.L.ModuleTypeSubstitution.id ty env + add_module_type t.Lang.ModuleTypeSubstitution.id ty env let inherit_resolver env = match env.resolver with Some r -> set_resolver empty r | None -> empty @@ -794,7 +800,7 @@ let open_units resolver env = env resolver.open_units let env_of_unit t ~linking resolver = - let open Odoc_model.Lang.Compilation_unit in + let open Lang.Compilation_unit in let initial_env = let m = module_of_unit t in let dm = Component.Delayed.put (fun () -> m) in @@ -803,7 +809,7 @@ let env_of_unit t ~linking resolver = in set_resolver initial_env resolver |> open_units resolver -let open_page page env = add_docs page.Odoc_model.Lang.Page.content env +let open_page page env = add_docs page.Lang.Page.content env let env_of_page page resolver = let initial_env = open_page page empty in diff --git a/src/xref2/env.mli b/src/xref2/env.mli index 0058828d27..b72fe8bcca 100644 --- a/src/xref2/env.mli +++ b/src/xref2/env.mli @@ -1,22 +1,27 @@ (* Env.mli *) +open Odoc_model open Odoc_model.Paths type lookup_unit_result = | Forward_reference - | Found of Odoc_model.Lang.Compilation_unit.t + | Found of Lang.Compilation_unit.t | Not_found -type lookup_page_result = Odoc_model.Lang.Page.t option +type lookup_page_result = Lang.Page.t option type root = - | Resolved of (Odoc_model.Root.t * Identifier.Module.t * Component.Module.t) + | Resolved of + (Root.t * Odoc_model.Paths.Identifier.Module.t * Component.Module.t) | Forward type resolver = { open_units : string list; lookup_unit : string -> lookup_unit_result; lookup_page : string -> lookup_page_result; + lookup_def : Identifier.t -> Lang.Locations.t option; + (** Lookup the source code location from an identifier. Returns + [Some (source_parent, anchor)] when definition is found. *) } type lookup_type = @@ -71,9 +76,9 @@ val add_exception : Identifier.Exception.t -> Component.Exception.t -> t -> t val add_extension_constructor : Identifier.Extension.t -> Component.Extension.Constructor.t -> t -> t -val add_docs : Odoc_model.Comment.docs -> t -> t +val add_docs : Comment.docs -> t -> t -val add_comment : Odoc_model.Comment.docs_or_stop -> t -> t +val add_comment : Comment.docs_or_stop -> t -> t val add_method : Identifier.Method.t -> Component.Method.t -> t -> t @@ -85,12 +90,19 @@ val add_module_type_functor_args : val lookup_fragment_root : t -> (int * Component.Signature.t) option -val lookup_page : string -> t -> Odoc_model.Lang.Page.t option +val lookup_page : string -> t -> Lang.Page.t option -val module_of_unit : Odoc_model.Lang.Compilation_unit.t -> Component.Module.t +val lookup_unit : string -> t -> lookup_unit_result option + +val module_of_unit : Lang.Compilation_unit.t -> Component.Module.t val lookup_root_module : string -> t -> root option +val lookup_def : + [< Identifier.t_pv ] Paths.Identifier.id -> t -> Lang.Locations.t option +(** Lookup the definition of the given identifier. Returns the root module and + the anchor. *) + type 'a scope constraint 'a = [< Component.Element.any ] (** Target of a lookup *) @@ -103,10 +115,7 @@ val lookup_by_name : 'a scope -> string -> t -> 'a maybe_ambiguous name. *) val lookup_by_id : - 'a scope -> - [< Identifier.t_pv ] Odoc_model.Paths.Identifier.id -> - t -> - 'a option + 'a scope -> [< Identifier.t_pv ] Paths.Identifier.id -> t -> 'a option (** Like [lookup_by_name] but use an identifier as key. *) val s_any : Component.Element.any scope @@ -140,29 +149,27 @@ val s_field : Component.Element.field scope val s_label_parent : Component.Element.label_parent scope (* val open_component_signature : - Odoc_model.Paths_types.Identifier.signature -> Component.Signature.t -> t -> t *) + Paths_types.Identifier.signature -> Component.Signature.t -> t -> t *) -val add_functor_parameter : Odoc_model.Lang.FunctorParameter.t -> t -> t +val add_functor_parameter : Lang.FunctorParameter.t -> t -> t -val open_class_signature : Odoc_model.Lang.ClassSignature.t -> t -> t +val open_class_signature : Lang.ClassSignature.t -> t -> t -val open_signature : Odoc_model.Lang.Signature.t -> t -> t +val open_signature : Lang.Signature.t -> t -> t -val open_type_substitution : Odoc_model.Lang.TypeDecl.t -> t -> t +val open_type_substitution : Lang.TypeDecl.t -> t -> t -val open_module_substitution : Odoc_model.Lang.ModuleSubstitution.t -> t -> t +val open_module_substitution : Lang.ModuleSubstitution.t -> t -> t -val open_module_type_substitution : - Odoc_model.Lang.ModuleTypeSubstitution.t -> t -> t +val open_module_type_substitution : Lang.ModuleTypeSubstitution.t -> t -> t -val open_page : Odoc_model.Lang.Page.t -> t -> t +val open_page : Lang.Page.t -> t -> t (** Add a page content to the env. *) -val env_of_unit : - Odoc_model.Lang.Compilation_unit.t -> linking:bool -> resolver -> t +val env_of_unit : Lang.Compilation_unit.t -> linking:bool -> resolver -> t (** Create a new env with a module initially opened. *) -val env_of_page : Odoc_model.Lang.Page.t -> resolver -> t +val env_of_page : Lang.Page.t -> resolver -> t (** Create a new env for a page. *) val env_for_reference : resolver -> t diff --git a/src/xref2/errors.ml b/src/xref2/errors.ml index bd67324872..18515fc56f 100644 --- a/src/xref2/errors.ml +++ b/src/xref2/errors.ml @@ -292,7 +292,8 @@ type what = | `With_type of Cfrag.type_ | `Module_type_expr of Component.ModuleType.expr | `Module_type_u_expr of Component.ModuleType.U.expr - | `Child of Reference.t + | `Child_module of string + | `Child_page of string | `Reference of Reference.t ] let report ~(what : what) ?tools_error action = @@ -339,7 +340,8 @@ let report ~(what : what) ?tools_error action = r "module type expression" module_type_expr cexpr | `Module_type_u_expr cexpr -> r "module type u expression" u_module_type_expr cexpr - | `Child rf -> r "child reference" model_reference rf + | `Child_module rf -> r "child module" Astring.String.pp rf + | `Child_page rf -> r "child page" Astring.String.pp rf | `Reference ref -> r "reference" model_reference ref in match kind_of_error ~what tools_error with diff --git a/src/xref2/find.ml b/src/xref2/find.ml index 70f843f739..354a022bdc 100644 --- a/src/xref2/find.ml +++ b/src/xref2/find.ml @@ -82,6 +82,13 @@ let filter_in_sig sg f = in inner f sg.Signature.items +(** Returns the last element of a list. Used to implement [_unambiguous] + functions. *) +let rec disambiguate = function + | [ x ] -> Some x + | [] -> None + | _ :: tl -> disambiguate tl + let module_in_sig sg name = find_in_sig sg (function | Signature.Module (id, _, m) when N.module_ id = name -> @@ -104,14 +111,6 @@ let type_in_sig sg name = Some (`FClassType (N.class_type' id, c)) | _ -> None) -let class_in_sig sg name = - find_in_sig sg (function - | Signature.Class (id, _, c) when N.class_ id = name -> - Some (`FClass (N.class' id, c)) - | Signature.ClassType (id, _, c) when N.class_type id = name -> - Some (`FClassType (N.class_type' id, c)) - | _ -> None) - type removed_type = [ `FType_removed of TypeName.t * TypeExpr.t * TypeDecl.Equation.t ] @@ -157,11 +156,6 @@ let careful_type_in_sig sg name = | Some _ as x -> x | None -> removed_type_in_sig sg name -let careful_class_in_sig sg name = - match class_in_sig sg name with - | Some _ as x -> x - | None -> removed_type_in_sig sg name - let datatype_in_sig sg name = find_in_sig sg (function | Signature.Type (id, _, t) when N.type_ id = name -> @@ -176,6 +170,13 @@ let class_in_sig sg name = Some (`FClassType (N.class_type' id, c)) | _ -> None) +let class_in_sig_unambiguous sg name = disambiguate (class_in_sig sg name) + +let careful_class_in_sig sg name = + match class_in_sig_unambiguous sg name with + | Some _ as x -> x + | None -> removed_type_in_sig sg name + let any_in_type (typ : TypeDecl.t) name = let rec find_cons = function | ({ TypeDecl.Constructor.name = name'; _ } as cons) :: _ when name' = name @@ -265,6 +266,8 @@ let value_in_sig sg name = Some (`FValue (N.typed_value id, Delayed.get m)) | _ -> None) +let value_in_sig_unambiguous sg name = disambiguate (value_in_sig sg name) + let label_in_sig sg name = filter_in_sig sg (function | Signature.Comment (`Docs d) -> any_in_comment d name diff --git a/src/xref2/find.mli b/src/xref2/find.mli index 26e9049889..c515ed4fe3 100644 --- a/src/xref2/find.mli +++ b/src/xref2/find.mli @@ -96,6 +96,12 @@ val any_in_type_in_sig : Signature.t -> string -> any_in_type_in_sig list val any_in_class_signature : ClassSignature.t -> string -> any_in_class_sig list +(** Disambiguated lookups, returns the last match. *) + +val class_in_sig_unambiguous : Signature.t -> string -> class_ option + +val value_in_sig_unambiguous : Signature.t -> string -> value option + (** Lookup removed items *) type removed_type = diff --git a/src/xref2/lang_of.ml b/src/xref2/lang_of.ml index eb1f89a7b5..4d838d4404 100644 --- a/src/xref2/lang_of.ml +++ b/src/xref2/lang_of.ml @@ -478,6 +478,7 @@ and class_ map parent id c = in { id = identifier; + locs = c.locs; doc = docs (parent :> Identifier.LabelParent.t) c.doc; virtual_ = c.virtual_; params = c.params; @@ -515,6 +516,7 @@ and class_type map parent id c = in { Odoc_model.Lang.ClassType.id = identifier; + locs = c.locs; doc = docs (parent :> Identifier.LabelParent.t) c.doc; virtual_ = c.virtual_; params = c.params; @@ -663,6 +665,7 @@ and value_ map parent id v = let identifier = Identifier.Mk.value (parent, typed_name) in { id = identifier; + locs = v.locs; doc = docs (parent :> Identifier.LabelParent.t) v.doc; type_ = type_expr map (parent :> Identifier.Parent.t) v.type_; value = v.value; @@ -686,6 +689,7 @@ and extension_constructor map parent c = in { id = identifier; + locs = c.locs; doc = docs (parent :> Identifier.LabelParent.t) c.doc; args = type_decl_constructor_argument map (parent :> Identifier.Parent.t) c.args; @@ -702,6 +706,7 @@ and module_ map parent id m = let map = { map with shadowed = empty_shadow } in { Odoc_model.Lang.Module.id; + locs = m.locs; doc = docs (parent :> Identifier.LabelParent.t) m.doc; type_ = module_decl map identifier m.type_; canonical = m.canonical; @@ -840,6 +845,7 @@ and module_type : let map = { map with shadowed = empty_shadow } in { Odoc_model.Lang.ModuleType.id = identifier; + locs = mty.locs; doc = docs (parent :> Identifier.LabelParent.t) mty.doc; canonical = mty.canonical; expr = Opt.map (module_type_expr map sig_id) mty.expr; @@ -903,6 +909,7 @@ and type_decl map parent id (t : Component.TypeDecl.t) : let identifier = Component.TypeMap.find id map.type_ in { id = identifier; + locs = t.locs; equation = type_decl_equation map (parent :> Identifier.Parent.t) t.equation; doc = docs (parent :> Identifier.LabelParent.t) t.doc; canonical = t.canonical; @@ -1025,6 +1032,7 @@ and exception_ map parent id (e : Component.Exception.t) : in { id = identifier; + locs = e.locs; doc = docs (parent :> Identifier.LabelParent.t) e.doc; args = type_decl_constructor_argument map (parent :> Identifier.Parent.t) e.args; diff --git a/src/xref2/link.ml b/src/xref2/link.ml index edfbffd088..50893863bd 100644 --- a/src/xref2/link.ml +++ b/src/xref2/link.ml @@ -7,6 +7,9 @@ module Opt = struct let map f = function Some x -> Some (f x) | None -> None end +let locations env id locs = + match locs with Some _ as locs -> locs | None -> Env.lookup_def id env + (** Equivalent to {!Comment.synopsis}. *) let synopsis_from_comment (docs : Component.CComment.docs) = match docs with @@ -31,7 +34,9 @@ let synopsis_of_module env (m : Component.Module.t) = | Signature sg -> Ok sg in (* If there is no doc, look at the expansion. *) - match Tools.expansion_of_module env m >>= handle_expansion with + match + Tools.expansion_of_module env m >>= fun exp -> handle_expansion exp + with | Ok sg -> synopsis_from_comment (Component.extract_signature_doc sg) | Error _ -> None) @@ -66,6 +71,15 @@ let check_ambiguous_label ~loc env | xs -> ambiguous_label_warning label_name xs) | Ok _ | Error `Not_found -> () +let expansion_needed self target = + let self = (self :> Paths.Path.Resolved.t) in + let hidden_alias = Paths.Path.Resolved.is_hidden self + and self_canonical = + let i = Paths.Path.Resolved.identifier self in + i = (target :> Paths.Identifier.t) + in + self_canonical || hidden_alias + exception Loop let rec is_forward : Paths.Path.Module.t -> bool = function @@ -309,7 +323,9 @@ let rec unit env t = let open Compilation_unit in let content = match t.content with - | Module sg -> Module (signature env (t.id :> Id.Signature.t) sg) + | Module sg -> + let sg = signature env (t.id :> Id.Signature.t) sg in + Module sg | Pack _ as p -> p in { t with content; linked = true } @@ -318,6 +334,7 @@ and value_ env parent t = let open Value in { t with + locs = locations env (t.id :> Id.t) t.locs; doc = comment_docs env parent t.doc; type_ = type_expression env parent [] t.type_; } @@ -326,8 +343,9 @@ and exception_ env parent e = let open Exception in let res = Opt.map (type_expression env parent []) e.res in let args = type_decl_constructor_argument env parent e.args in + let locs = locations env e.id e.locs in let doc = comment_docs env parent e.doc in - { e with res; args; doc } + { e with locs; res; args; doc } and extension env parent t = let open Extension in @@ -335,6 +353,7 @@ and extension env parent t = let open Constructor in { c with + locs = locations env c.id c.locs; args = type_decl_constructor_argument env parent c.args; res = Opt.map (type_expression env parent []) c.res; doc = comment_docs env parent c.doc; @@ -355,7 +374,12 @@ and class_type_expr env parent = and class_type env parent c = let open ClassType in let doc = comment_docs env parent c.doc in - { c with expr = class_type_expr env parent c.expr; doc } + { + c with + locs = locations env c.id c.locs; + expr = class_type_expr env parent c.expr; + doc; + } and class_signature env parent c = let open ClassSignature in @@ -404,7 +428,9 @@ and class_ env parent c = Arrow (lbl, type_expression env parent [] expr, map_decl decl) in let doc = comment_docs env parent c.doc in - { c with type_ = map_decl c.type_; doc } + let locs = locations env c.id c.locs in + let type_ = map_decl c.type_ in + { c with locs; type_; doc } and module_substitution env parent m = let open ModuleSubstitution in @@ -475,15 +501,7 @@ and module_ : Env.t -> Module.t -> Module.t = let type_ = match type_ with | Alias (`Resolved p, _) -> - let hidden_alias = - Paths.Path.Resolved.Module.is_hidden ~weak_canonical_test:false p - in - let self_canonical = - let i = Paths.Path.Resolved.(identifier (p :> t)) in - i = (m.id :> Paths.Identifier.t) - in - let expansion_needed = self_canonical || hidden_alias in - if expansion_needed then + if expansion_needed p m.id then let cp = Component.Of_Lang.(resolved_module_path (empty ()) p) in match Tools.expansion_of_module_path ~strengthen:false env @@ -497,7 +515,9 @@ and module_ : Env.t -> Module.t -> Module.t = else type_ | Alias _ | ModuleType _ -> type_ in - { m with doc = comment_docs env sg_id m.doc; type_ } + let locs = (locations env (m.id :> Id.t)) m.locs in + let doc = comment_docs env sg_id m.doc in + { m with locs; doc; type_ } and module_decl : Env.t -> Id.Signature.t -> Module.decl -> Module.decl = fun env id decl -> @@ -530,7 +550,8 @@ and module_type : Env.t -> ModuleType.t -> ModuleType.t = | _ -> false in*) let doc = comment_docs env sg_id m.doc in - { m with expr = expr'; doc } + let locs = (locations env m.id) m.locs in + { m with locs; expr = expr'; doc } and module_type_substitution : Env.t -> ModuleTypeSubstitution.t -> ModuleTypeSubstitution.t = @@ -725,16 +746,7 @@ and module_type_expr : | Some e, _ -> Some (simple_expansion env (id :> Paths.Identifier.Signature.t) e) | None, Some (`Resolved p_path) -> - let hidden_alias = - Paths.Path.Resolved.ModuleType.is_hidden ~weak_canonical_test:false - p_path - in - let self_canonical = - let i = Paths.Path.Resolved.(identifier (p_path :> t)) in - (id :> Id.t) = i - in - let expansion_needed = self_canonical || hidden_alias in - if expansion_needed then + if expansion_needed p_path id then let cp = Component.Of_Lang.(resolved_module_type_path (empty ()) p_path) in @@ -805,6 +817,7 @@ and type_decl : Env.t -> Id.Signature.t -> TypeDecl.t -> TypeDecl.t = let open TypeDecl in let equation = type_decl_equation env parent t.equation in let doc = comment_docs env parent t.doc in + let locs = locations env t.id t.locs in let hidden_path = match equation.Equation.manifest with | Some (Constr (`Resolved path, params)) @@ -817,7 +830,7 @@ and type_decl : Env.t -> Id.Signature.t -> TypeDecl.t -> TypeDecl.t = let representation = Opt.map (type_decl_representation env parent) t.representation in - let default = { t with equation; doc; representation } in + let default = { t with locs; equation; doc; representation } in match hidden_path with | Some (p, params) -> ( let p' = Component.Of_Lang.(resolved_type_path (empty ()) p) in @@ -994,23 +1007,29 @@ and type_expression : Env.t -> Id.Signature.t -> _ -> _ = let link ~filename x y = Lookup_failures.catch_failures ~filename (fun () -> - if y.Lang.Compilation_unit.linked then y else unit x y) + if y.Lang.Compilation_unit.linked || y.hidden then y else unit x y) let page env page = - let children = - List.fold_right - (fun child res -> - match Ref_tools.resolve_reference env child |> Error.raise_warnings with - | Ok r -> `Resolved r :: res - | Error _ -> - Errors.report ~what:(`Child child) `Resolve; - res) - page.Odoc_model.Lang.Page.children [] + let () = + List.iter + (fun child -> + let check_resolves ~what f name = + match f name env with + | Some _ -> () + | None -> Errors.report ~what `Lookup + in + match child with + | Page.Source_tree_child _ -> () + | Page.Page_child page -> + check_resolves ~what:(`Child_page page) Env.lookup_page page + | Page.Module_child mod_ -> + check_resolves ~what:(`Child_module mod_) Env.lookup_root_module + mod_) + page.Lang.Page.children in { page with Page.content = comment_docs env page.Page.name page.content; - children; linked = true; } diff --git a/src/xref2/paths.md b/src/xref2/paths.md index 2aae2f3b76..3aea063698 100644 --- a/src/xref2/paths.md +++ b/src/xref2/paths.md @@ -434,7 +434,7 @@ val sg : Odoc_model.Lang.Signature.t = ihash = 818126955; ikey = "r_Root.p_None"}, ARG); ihash = 379411454; ikey = "mt_ARG.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -457,7 +457,7 @@ val sg : Odoc_model.Lang.Signature.t = ihash = 379411454; ikey = "mt_ARG.r_Root.p_None"}, S); ihash = 208722936; ikey = "mt_S.mt_ARG.r_Root.p_None"}; - doc = []; canonical = None; expr = None}]; + locs = None; doc = []; canonical = None; expr = None}]; compiled = true; doc = []})}; Odoc_model.Lang.Signature.Module (Odoc_model.Lang.Signature.Ordinary, {Odoc_model.Lang.Module.id = @@ -472,7 +472,7 @@ val sg : Odoc_model.Lang.Signature.t = ihash = 818126955; ikey = "r_Root.p_None"}, F); ihash = 748202139; ikey = "m_F.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Functor @@ -527,7 +527,8 @@ val sg : Odoc_model.Lang.Signature.t = S); ihash = 313393860; ikey = "mt_S.p_X.m_F.r_Root.p_None"}; - doc = []; canonical = None; expr = None}]; + locs = None; doc = []; canonical = None; + expr = None}]; compiled = true; doc = []}); p_path = `Resolved @@ -566,25 +567,25 @@ val sg : Odoc_model.Lang.Signature.t = F); ihash = 748202139; ikey = - "m_F.r_Root.p_No"... (* string length 17; truncated *)}; + "m_F.r_Root."... (* string length 17; truncated *)}; ihash = 709672416; ikey = - "___result__.m"... (* string length 29; truncated *)}, + "___result"... (* string length 29; truncated *)}, N); ihash = 837385364; - ikey = "m_N.___res"... (* string length 33; truncated *)}; - doc = []; + ikey = "m_N.___r"... (* string length 33; truncated *)}; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Path - {Odoc_model.Lang.ModuleType.p_expansion = None; - p_path = `Resolved ...}); - canonical = ...; hidden = ...}); - ...]; - compiled = ...; doc = ...})); - canonical = ...; hidden = ...}); - ...]; - compiled = ...; doc = ...} + {Odoc_model.Lang.ModuleType.p_expansion = ...; + p_path = ...}); + canonical = ...; hidden = ...}); + ...]; + compiled = ...; doc = ...})); + canonical = ...; hidden = ...}); + ...]; + compiled = ...; doc = ...} ``` The problem here is that odoc will not generate a page for the module `F(M)`. diff --git a/src/xref2/subst.ml b/src/xref2/subst.ml index 0873dceaec..9b1652c634 100644 --- a/src/xref2/subst.ml +++ b/src/xref2/subst.ml @@ -515,13 +515,7 @@ let list conv s xs = List.map (conv s) xs let rec type_ s t = let open Component.TypeDecl in let representation = option_ type_decl_representation s t.representation in - let canonical = t.canonical in - { - equation = type_decl_equation s t.equation; - representation; - doc = t.doc; - canonical; - } + { t with equation = type_decl_equation s t.equation; representation } and type_decl_representation s t = let open Component.TypeDecl.Representation in @@ -619,7 +613,7 @@ and module_type s t = let expr = match t.expr with Some m -> Some (module_type_expr s m) | None -> None in - { expr; doc = t.doc; canonical = t.canonical } + { expr; locs = t.locs; doc = t.doc; canonical = t.canonical } and module_type_substitution s t = let open Component.ModuleTypeSubstitution in @@ -804,7 +798,7 @@ and exception_ s e = let open Component.Exception in let res = option_ type_expr s e.res in let args = type_decl_constructor_arg s e.args in - { args; res; doc = e.doc } + { e with args; res } and extension_constructor s c = let open Component.Extension.Constructor in diff --git a/src/xref2/test.md b/src/xref2/test.md index 5bad520647..e55d7e7c3b 100644 --- a/src/xref2/test.md +++ b/src/xref2/test.md @@ -205,7 +205,7 @@ and so we simply look up the type in the environment, giving a `Component.Type.t ihash = 818126955; ikey = "r_Root.p_None"}, x); ihash = 622581103; ikey = "t_x.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -223,7 +223,7 @@ and so we simply look up the type in the environment, giving a `Component.Type.t ihash = 818126955; ikey = "r_Root.p_None"}, u); ihash = 15973539; ikey = "t_u.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = @@ -331,7 +331,7 @@ val path : Cpath.Resolved.module_ = val module_ : Component.Module.t Component.Delayed.t = {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Signature @@ -340,7 +340,8 @@ val module_ : Component.Module.t Component.Delayed.t = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.TypeDecl.doc = []; canonical = None; + {Odoc_xref2.Component.TypeDecl.locs = None; doc = []; + canonical = None; equation = {Odoc_xref2.Component.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -362,7 +363,8 @@ Odoc_xref2.Tools.Signature Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.TypeDecl.doc = []; canonical = None; + {Odoc_xref2.Component.TypeDecl.locs = None; doc = []; + canonical = None; equation = {Odoc_xref2.Component.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -416,7 +418,7 @@ val path : Cpath.Resolved.module_ = val module_ : Component.Module.t Component.Delayed.t = {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -482,7 +484,8 @@ val m : Component.Element.module_type option = ihash = 818126955; ikey = "r_Root.p_None"}, M); ihash = 459143770; ikey = "mt_M.r_Root.p_None"}, - {Odoc_xref2.Component.ModuleType.doc = []; canonical = None; + {Odoc_xref2.Component.ModuleType.locs = None; doc = []; + canonical = None; expr = Some (Odoc_xref2.Component.ModuleType.Signature @@ -491,7 +494,7 @@ val m : Component.Element.module_type option = (`LModuleType (N, 1), {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.ModuleType.doc = []; + {Odoc_xref2.Component.ModuleType.locs = None; doc = []; canonical = None; expr = Some @@ -502,8 +505,8 @@ val m : Component.Element.module_type option = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.TypeDecl.doc = []; - canonical = None; + {Odoc_xref2.Component.TypeDecl.locs = None; + doc = []; canonical = None; equation = {Odoc_xref2.Component.TypeDecl.Equation.params = []; @@ -517,7 +520,7 @@ val m : Component.Element.module_type option = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -835,7 +838,7 @@ val module_C_lens : ihash = 818126955; ikey = "r_Root.p_None"}, C); ihash = 43786577; ikey = "m_C.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.With @@ -883,7 +886,7 @@ of module `C` we see the following: val m : Component.Module.t Component.Delayed.t = {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.With @@ -936,7 +939,7 @@ val sg : Tools.expansion = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.Alias (`Identifier @@ -959,7 +962,7 @@ val sg : Tools.expansion = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -979,7 +982,7 @@ look up module `N` from within this and find its signature: val m : Component.Module.t Component.Delayed.t = {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -1014,7 +1017,8 @@ Odoc_xref2.Tools.Signature Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.TypeDecl.doc = []; canonical = None; + {Odoc_xref2.Component.TypeDecl.locs = None; doc = []; + canonical = None; equation = {Odoc_xref2.Component.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -1503,7 +1507,7 @@ val p : Cpath.Resolved.module_ = val m : Component.Module.t Component.Delayed.t = {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -1555,7 +1559,7 @@ val sg' : Tools.expansion = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -1592,7 +1596,7 @@ val sg' : Tools.expansion = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -1629,7 +1633,7 @@ val sg' : Tools.expansion = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -1666,7 +1670,7 @@ val sg' : Tools.expansion = Odoc_model.Lang.Signature.Ordinary, {Odoc_xref2.Component.Delayed.v = Some - {Odoc_xref2.Component.Module.doc = []; + {Odoc_xref2.Component.Module.locs = None; doc = []; type_ = Odoc_xref2.Component.Module.ModuleType (Odoc_xref2.Component.ModuleType.Path @@ -2435,6 +2439,7 @@ let resolved = Common.compile_signature sg;; ihash = 818126955; ikey = "r_Root.p_None"}, t); ihash = 1016576344; ikey = "t_t.r_Root.p_None"}; + locs = None; doc = [{Odoc_model__.Location_.location = {Odoc_model__.Location_.file = ""; @@ -2498,7 +2503,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 818126955; ikey = "r_Root.p_None"}, M); ihash = 459143770; ikey = "mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -2522,7 +2527,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 459143770; ikey = "mt_M.r_Root.p_None"}, t); ihash = 825731485; ikey = "t_t.mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -2541,7 +2546,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 818126955; ikey = "r_Root.p_None"}, u); ihash = 15973539; ikey = "t_u.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -2559,7 +2564,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 818126955; ikey = "r_Root.p_None"}, M1); ihash = 756272831; ikey = "mt_M1.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.With @@ -2649,7 +2654,7 @@ Odoc_model.Lang.ModuleType.Path ihash = 716453475; ikey = "m_M.r_Root.p_None"}, s); ihash = 395135148; ikey = "t_s.m_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -2804,7 +2809,7 @@ let m_e_i_s_value mod_name n val_name = ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, id); ihash = 424389437; ikey = "v_id.m_Foo3.r_Root.p_None"}; - doc = []; + locs = None; value = Odoc_model.Lang.Value.Abstract; doc = []; type_ = Odoc_model.Lang.TypeExpr.Constr (`Dot @@ -2822,8 +2827,7 @@ let m_e_i_s_value mod_name n val_name = ihash = 249248993; ikey = "m_Foo.r_Root.p_None"}, false), "t"), - []); - value = Odoc_model.Lang.Value.Abstract} + [])} # Common.LangUtils.Lens.get (m_e_i_s_value "Foo3" 0 "id2") sg;; - : Odoc_model.Lang.Value.t = {Odoc_model.Lang.Value.id = @@ -2842,7 +2846,7 @@ let m_e_i_s_value mod_name n val_name = ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, id2); ihash = 412619918; ikey = "v_id2.m_Foo3.r_Root.p_None"}; - doc = []; + locs = None; value = Odoc_model.Lang.Value.Abstract; doc = []; type_ = Odoc_model.Lang.TypeExpr.Constr (`Identifier @@ -2862,8 +2866,7 @@ let m_e_i_s_value mod_name n val_name = {t}3); ihash = 271372153; ikey = "t_{t}3.m_Foo3.r_Root.p_None"}, false), - []); - value = Odoc_model.Lang.Value.Abstract} + [])} ``` @@ -2914,7 +2917,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, {t}4); ihash = 671044364; ikey = "t_{t}4.m_Foo3.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = @@ -2955,7 +2958,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, id); ihash = 424389437; ikey = "v_id.m_Foo3.r_Root.p_None"}; - doc = []; + locs = None; value = Odoc_model.Lang.Value.Abstract; doc = []; type_ = Odoc_model.Lang.TypeExpr.Constr (`Identifier @@ -2975,8 +2978,7 @@ let sg = Common.signature_of_mli_string test_data;; {t}4); ihash = 671044364; ikey = "t_{t}4.m_Foo3.r_Root.p_None"}, false), - []); - value = Odoc_model.Lang.Value.Abstract}]; + [])}]; compiled = false; doc = []} # Common.LangUtils.Lens.get (module_expansion_include_sig "Foo3" 1) sg;; - : Odoc_model.Lang.Signature.t = @@ -2998,7 +3000,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, {t}5); ihash = 67089224; ikey = "t_{t}5.m_Foo3.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = @@ -3039,7 +3041,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, id2); ihash = 412619918; ikey = "v_id2.m_Foo3.r_Root.p_None"}; - doc = []; + locs = None; value = Odoc_model.Lang.Value.Abstract; doc = []; type_ = Odoc_model.Lang.TypeExpr.Constr (`Identifier @@ -3059,8 +3061,7 @@ let sg = Common.signature_of_mli_string test_data;; {t}5); ihash = 67089224; ikey = "t_{t}5.m_Foo3.r_Root.p_None"}, false), - []); - value = Odoc_model.Lang.Value.Abstract}]; + [])}]; compiled = false; doc = []} ``` @@ -3114,7 +3115,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, {t}6); ihash = 133032212; ikey = "t_{t}6.m_Foo3.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = @@ -3155,15 +3156,14 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, {x}7); ihash = 314949087; ikey = "v_{x}7.m_Foo3.r_Root.p_None"}; - doc = []; + locs = None; value = Odoc_model.Lang.Value.Abstract; doc = []; type_ = Odoc_model.Lang.TypeExpr.Constr (`Identifier ({Odoc_model__Paths_types.iv = `CoreType int; ihash = 432452609; ikey = "coret_int"}, false), - []); - value = Odoc_model.Lang.Value.Abstract}; + [])}; Odoc_model.Lang.Signature.Value {Odoc_model.Lang.Value.id = {Odoc_model__Paths_types.iv = @@ -3181,7 +3181,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, id); ihash = 424389437; ikey = "v_id.m_Foo3.r_Root.p_None"}; - doc = []; + locs = None; value = Odoc_model.Lang.Value.Abstract; doc = []; type_ = Odoc_model.Lang.TypeExpr.Constr (`Identifier @@ -3201,8 +3201,7 @@ let sg = Common.signature_of_mli_string test_data;; {t}6); ihash = 133032212; ikey = "t_{t}6.m_Foo3.r_Root.p_None"}, false), - []); - value = Odoc_model.Lang.Value.Abstract}]; + [])}]; compiled = false; doc = []} ``` @@ -3255,7 +3254,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, {Bar}9); ihash = 658027043; ikey = "m_{Bar}9.m_Foo3.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.Alias (`Dot @@ -3292,7 +3291,7 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 670280318; ikey = "m_Foo3.r_Root.p_None"}, id); ihash = 424389437; ikey = "v_id.m_Foo3.r_Root.p_None"}; - doc = []; + locs = None; value = Odoc_model.Lang.Value.Abstract; doc = []; type_ = Odoc_model.Lang.TypeExpr.Constr (`Dot @@ -3315,7 +3314,6 @@ let sg = Common.signature_of_mli_string test_data;; ihash = 658027043; ikey = "m_{Bar}9.m_Foo3.r_Root.p_None"}, true), "t"), - []); - value = Odoc_model.Lang.Value.Abstract}]; + [])}]; compiled = false; doc = []} ``` diff --git a/src/xref2/type_of.ml b/src/xref2/type_of.ml index b9d2b7b278..844d6da385 100644 --- a/src/xref2/type_of.ml +++ b/src/xref2/type_of.ml @@ -94,8 +94,8 @@ and module_type_expr_typeof env (id : Id.Signature.t) t = let cp = Component.Of_Lang.(module_path (empty ()) p) in let open Expand_tools in let open Utils.ResultMonad in - Tools.expansion_of_module_path env ~strengthen cp >>= handle_expansion env id - >>= fun (_env, e) -> Ok e + Tools.expansion_of_module_path env ~strengthen cp >>= fun exp -> + handle_expansion env id exp >>= fun (_env, e) -> Ok e and module_type_expr env (id : Id.Signature.t) expr = match expr with diff --git a/src/xref2/utils.ml b/src/xref2/utils.ml index 52e6215eac..9c5b764f26 100644 --- a/src/xref2/utils.ml +++ b/src/xref2/utils.ml @@ -41,3 +41,15 @@ module EitherMonad = struct let of_result = function Result.Ok x -> Right x | Error y -> Left y end + +let rec concat_map acc f = function + | hd :: tl -> concat_map (List.rev_append (f hd) acc) f tl + | [] -> List.rev acc + +let rec filter_map acc f = function + | hd :: tl -> + let acc = match f hd with Some x -> x :: acc | None -> acc in + filter_map acc f tl + | [] -> List.rev acc + +let option_value ~default v = match v with None -> default | Some v -> v diff --git a/test/integration/dune b/test/integration/dune index 6ed1ffbdbb..1bf1d8d217 100644 --- a/test/integration/dune +++ b/test/integration/dune @@ -1,3 +1,8 @@ (cram (deps (package odoc))) + +(cram + (applies_to json_expansion_with_sources) + (enabled_if + (= %{ocaml_version} 4.14.0))) diff --git a/test/integration/html_opts.t/run.t b/test/integration/html_opts.t/run.t index e603abceb0..7bb00136dc 100644 --- a/test/integration/html_opts.t/run.t +++ b/test/integration/html_opts.t/run.t @@ -22,7 +22,7 @@ Generate --as-json embeddable HTML fragment output: $ odoc html-generate test.odocl -o html --as-json --indent $ cat html/test/Test/index.html.json - {"uses_katex":false,"breadcrumbs":[{"name":"test","href":"../index.html","kind":"page"},{"name":"Test","href":"#","kind":"module"}],"toc":[{"title":"Section 1","href":"#section-1","children":[]},{"title":"Section 2","href":"#section-2","children":[]}],"preamble":"

Test

","content":"

Section 1

\u000A
\u000A \u000A type t\u000A
\u000A

Section 2

\u000A
\u000A \u000A type u\u000A
\u000A
"} + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"test","href":"../index.html","kind":"page"},{"name":"Test","href":"#","kind":"module"}],"toc":[{"title":"Section 1","href":"#section-1","children":[]},{"title":"Section 2","href":"#section-2","children":[]}],"source_anchor":null,"preamble":"

Test

","content":"

Section 1

\u000A
\u000A \u000A type t\u000A
\u000A

Section 2

\u000A
\u000A \u000A type u\u000A
\u000A
"} $ odoc html-targets test.odocl -o html --as-json --indent html/test/Test/index.html.json diff --git a/test/integration/json_expansion.t/run.t b/test/integration/json_expansion.t/run.t index 39fa6dfc72..4a263a1149 100644 --- a/test/integration/json_expansion.t/run.t +++ b/test/integration/json_expansion.t/run.t @@ -18,10 +18,10 @@ Test the JSON output in the presence of expanded modules. $ odoc html-generate --as-json -o html main.odocl $ cat html/Main/index.html.json - {"uses_katex":false,"breadcrumbs":[{"name":"Main","href":"#","kind":"module"}],"toc":[],"preamble":"","content":"
module A : sig ... end
"} + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"#","kind":"module"}],"toc":[],"source_anchor":null,"preamble":"","content":"
module A : sig ... end
"} $ cat html/Main/A/index.html.json - {"uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../index.html","kind":"module"},{"name":"A","href":"#","kind":"module"}],"toc":[],"preamble":"","content":"
module B : sig ... end
"} + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../index.html","kind":"module"},{"name":"A","href":"#","kind":"module"}],"toc":[],"source_anchor":null,"preamble":"","content":"
module B : sig ... end
"} $ cat html/Main/A/B/index.html.json - {"uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../../index.html","kind":"module"},{"name":"A","href":"../index.html","kind":"module"},{"name":"B","href":"#","kind":"module"}],"toc":[],"preamble":"","content":""} + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../../index.html","kind":"module"},{"name":"A","href":"../index.html","kind":"module"},{"name":"B","href":"#","kind":"module"}],"toc":[],"source_anchor":null,"preamble":"","content":""} diff --git a/test/integration/json_expansion_with_sources.t/a.ml b/test/integration/json_expansion_with_sources.t/a.ml new file mode 100644 index 0000000000..6c5699e6c8 --- /dev/null +++ b/test/integration/json_expansion_with_sources.t/a.ml @@ -0,0 +1 @@ +module B = struct end diff --git a/test/integration/json_expansion_with_sources.t/main.ml b/test/integration/json_expansion_with_sources.t/main.ml new file mode 100644 index 0000000000..ceccbfa0a1 --- /dev/null +++ b/test/integration/json_expansion_with_sources.t/main.ml @@ -0,0 +1,2 @@ +module A = Main__A +(** @canonical Main.A *) diff --git a/test/integration/json_expansion_with_sources.t/root.mld b/test/integration/json_expansion_with_sources.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/integration/json_expansion_with_sources.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/integration/json_expansion_with_sources.t/run.t b/test/integration/json_expansion_with_sources.t/run.t new file mode 100644 index 0000000000..1479ef0ca1 --- /dev/null +++ b/test/integration/json_expansion_with_sources.t/run.t @@ -0,0 +1,44 @@ +Test the JSON output in the presence of expanded modules. + + $ odoc compile --child module-a --child src-source root.mld + + $ printf "a.ml\nmain.ml\n" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + + $ ocamlc -c -bin-annot -o main__A.cmo a.ml -I . + $ ocamlc -c -bin-annot main.ml -I . + $ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . main__A.cmt + $ odoc compile --source-name main.ml --source-parent-file src-source.odoc -I . main.cmt + $ odoc link -I . main__A.odoc + $ odoc link -I . main.odoc + + $ odoc html-targets --source a.ml -o html main__A.odocl + html/root/source/a.ml.html + $ odoc html-targets --source main.ml -o html main.odocl + html/Main/index.html + html/Main/A/index.html + html/Main/A/B/index.html + html/root/source/main.ml.html + $ odoc html-targets --source a.ml --as-json -o html main__A.odocl + html/root/source/a.ml.html.json + $ odoc html-targets --source main.ml --as-json -o html main.odocl + html/Main/index.html.json + html/Main/A/index.html.json + html/Main/A/B/index.html.json + html/root/source/main.ml.html.json + + $ odoc html-generate --source a.ml --as-json -o html main__A.odocl + $ odoc html-generate --source main.ml --as-json -o html main.odocl + + $ cat html/Main/index.html.json + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"#","kind":"module"}],"toc":[],"source_anchor":"../root/source/main.ml.html","preamble":"","content":"
Sourcemodule A : sig ... end
"} + + $ cat html/Main/A/index.html.json + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../index.html","kind":"module"},{"name":"A","href":"#","kind":"module"}],"toc":[],"source_anchor":"../../root/source/a.ml.html","preamble":"","content":"
Sourcemodule B : sig ... end
"} + + $ cat html/Main/A/B/index.html.json + {"type":"documentation","uses_katex":false,"breadcrumbs":[{"name":"Main","href":"../../index.html","kind":"module"},{"name":"A","href":"../index.html","kind":"module"},{"name":"B","href":"#","kind":"module"}],"toc":[],"source_anchor":"../../../root/source/a.ml.html#def-0","preamble":"","content":""} + + $ cat html/root/source/a.ml.html.json + {"type":"source","breadcrumbs":[{"name":"root","href":"../index.html","kind":"page"},{"name":"source","href":"index.html","kind":"page"},{"name":"a.ml","href":"#","kind":"source"}],"content":"
1\u000Amodule B = struct end\u000A
"} diff --git a/test/odoc_print/odoc_print.ml b/test/odoc_print/odoc_print.ml index 9389e27e3e..66c47eb1f1 100644 --- a/test/odoc_print/odoc_print.ml +++ b/test/odoc_print/odoc_print.ml @@ -1,8 +1,8 @@ (** Print .odocl files. *) open Odoc_odoc +open Odoc_odoc.Or_error open Odoc_model_desc -open Or_error let print_json_desc desc x = let yojson = Type_desc_to_yojson.to_yojson desc x in @@ -167,10 +167,13 @@ let run inp ref = let inp = Fpath.v inp in Odoc_file.load inp >>= fun unit -> match unit.content with + | Odoc_file.Source_tree_content tree -> + print_json_desc Lang_desc.source_tree_page_t tree; + Ok () | Odoc_file.Page_content page -> print_json_desc Lang_desc.page_t page; Ok () - | Unit_content u -> ( + | Unit_content (u, _) -> ( match ref with | None -> print_json_desc Lang_desc.compilation_unit_t u; diff --git a/test/pages/errors.t/run.t b/test/pages/errors.t/run.t index cf73a9d2e1..f899f0ddda 100644 --- a/test/pages/errors.t/run.t +++ b/test/pages/errors.t/run.t @@ -5,16 +5,12 @@ Let's check for expected errors. This is the top1 page. We need to match parents with children - $ odoc compile top1.mld + $ odoc compile -c dummy top1.mld $ odoc compile -I . --parent top1 sub1.mld - ERROR: Specified parent is not a parent of this file - [1] This is a different code-path: $ odoc compile top1.mld --child foo $ odoc compile -I . --parent top1 sub1.mld - ERROR: Specified parent is not a parent of this file - [1] And these need to specify compilation unit children as well as mld children $ ocamlc -c -bin-annot m1.mli @@ -24,7 +20,7 @@ And these need to specify compilation unit children as well as mld children [1] Parents must be pages - $ odoc compile top1.mld --child m1 + $ odoc compile top1.mld --child M1 $ odoc compile m1.cmti -I . --parent top1 $ odoc compile sub1.mld -I . --parent module-M1 ERROR: Expecting page as parent @@ -34,5 +30,5 @@ Linking checks the children are all present: $ odoc compile top1.mld --child foo $ odoc link page-top1.odoc -I . File "page-top1.odoc": - Warning: Failed to resolve child reference unresolvedroot(foo) + Warning: Failed to lookup child page foo diff --git a/test/pages/references.t/run.t b/test/pages/references.t/run.t index 16db73f3cc..47ef002064 100644 --- a/test/pages/references.t/run.t +++ b/test/pages/references.t/run.t @@ -3,7 +3,7 @@ $ ocamlc -c -bin-annot foo.mli $ ocamlc -c -bin-annot moo.mli - $ odoc compile page.mld --child bar --child module-baz --child Foo --child module-Moo + $ odoc compile page.mld --child Bar --child module-baz --child Foo --child module-Moo $ odoc compile Bar.cmti -I . --parent page $ odoc compile Baz.cmti -I . --parent page-page $ odoc compile foo.cmti -I . --parent page diff --git a/test/pages/resolution.t/run.t b/test/pages/resolution.t/run.t index 3b3a01088c..1cd275557d 100644 --- a/test/pages/resolution.t/run.t +++ b/test/pages/resolution.t/run.t @@ -16,7 +16,7 @@ Check resolution works $ ocamlc -c -bin-annot m1.mli $ odoc compile top1.mld --child page-sub1 --child page-sub2 - $ odoc compile sub1.mld -I . --parent top1 --child m1 + $ odoc compile sub1.mld -I . --parent top1 --child M1 $ odoc compile sub2.mld -I . --parent top1 --child page-m1 $ odoc compile m1.cmti -I . --parent sub1 $ odoc compile m1.mld -I . --parent sub2 diff --git a/test/pages/tree.t/run.t b/test/pages/tree.t/run.t index ce7702d80b..5f7ed0461c 100644 --- a/test/pages/tree.t/run.t +++ b/test/pages/tree.t/run.t @@ -42,9 +42,9 @@ Compile the modules: Now compile the pages: $ odoc compile top1.mld --child page-sub1 $ odoc compile top2.mld --child page-sub2 - $ odoc compile sub1.mld -I . --parent top1 --child page-sub3 --child m1 - $ odoc compile sub2.mld -I . --parent top2 --child m2 - $ odoc compile sub3.mld -I . --parent sub1 --child m3 + $ odoc compile sub1.mld -I . --parent top1 --child page-sub3 --child M1 + $ odoc compile sub2.mld -I . --parent top2 --child M2 + $ odoc compile sub3.mld -I . --parent sub1 --child M3 $ odoc compile m1.cmti -I . --parent sub1 $ odoc compile m2.cmti -I . --parent sub2 $ odoc compile m3.cmti -I . --parent sub3 diff --git a/test/sources/double_wrapped.t/a.ml b/test/sources/double_wrapped.t/a.ml new file mode 100644 index 0000000000..0547b3d0ee --- /dev/null +++ b/test/sources/double_wrapped.t/a.ml @@ -0,0 +1 @@ +let x = 1 diff --git a/test/sources/double_wrapped.t/main.ml b/test/sources/double_wrapped.t/main.ml new file mode 100644 index 0000000000..085a2c415e --- /dev/null +++ b/test/sources/double_wrapped.t/main.ml @@ -0,0 +1,3 @@ +(** Handwritten top-level module *) + +module A = A diff --git a/test/sources/double_wrapped.t/main__.ml b/test/sources/double_wrapped.t/main__.ml new file mode 100644 index 0000000000..63bb86e4b2 --- /dev/null +++ b/test/sources/double_wrapped.t/main__.ml @@ -0,0 +1,4 @@ +(** Would be generated by dune *) + +module A = Main__A +(** @canonical Main.A *) diff --git a/test/sources/double_wrapped.t/root.mld b/test/sources/double_wrapped.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/double_wrapped.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/double_wrapped.t/run.t b/test/sources/double_wrapped.t/run.t new file mode 100644 index 0000000000..bcb76c68ed --- /dev/null +++ b/test/sources/double_wrapped.t/run.t @@ -0,0 +1,67 @@ +This is what happens when a dune user write a toplevel module. +Similar to the lookup_def_wrapped test. + + $ odoc compile -c module-a -c src-source root.mld + + $ printf "a.ml\nmain.ml\n" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + $ ocamlc -c -o main__A.cmo a.ml -bin-annot -I . + $ ocamlc -c -o main__.cmo main__.ml -bin-annot -I . + $ ocamlc -c -open Main__ main.ml -bin-annot -I . + + $ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . main__A.cmt + $ odoc compile -I . main__.cmt + $ odoc compile --source-name main.ml --source-parent-file src-source.odoc -I . main.cmt + + $ odoc link -I . main.odoc + $ odoc link -I . main__A.odoc + $ odoc link -I . main__.odoc + + $ odoc html-generate --source main.ml --indent -o html main.odocl + $ odoc html-generate --hidden --indent -o html main__.odocl + $ odoc html-generate --source a.ml --hidden --indent -o html main__A.odocl + +Look if all the source files are generated: + + $ find html | sort + html + html/Main + html/Main/A + html/Main/A/index.html + html/Main/index.html + html/root + html/root/source + html/root/source/a.ml.html + html/root/source/main.ml.html + + $ cat html/Main/A/index.html + + + A (Main.A) + + + + + + + + +
+

Module Main.A + Source +

+
+
+
+
+ + Source + val x : int +
+
+
+ + diff --git a/test/sources/dune b/test/sources/dune new file mode 100644 index 0000000000..d407bf69ff --- /dev/null +++ b/test/sources/dune @@ -0,0 +1,11 @@ +; Tests related to linking to source code + +(env + (_ + (binaries + (../odoc_print/odoc_print.exe as odoc_print)))) + +(cram + (enabled_if + (= %{ocaml_version} 4.14.0)) + (deps %{bin:odoc} %{bin:odoc_print})) diff --git a/test/sources/functor.t/a.ml b/test/sources/functor.t/a.ml new file mode 100644 index 0000000000..b2493ac95d --- /dev/null +++ b/test/sources/functor.t/a.ml @@ -0,0 +1,4 @@ +module F (S : S.S) = struct + type t = S.t + let y = S.x +end diff --git a/test/sources/functor.t/b.ml b/test/sources/functor.t/b.ml new file mode 100644 index 0000000000..d0d080e8a8 --- /dev/null +++ b/test/sources/functor.t/b.ml @@ -0,0 +1,7 @@ +module S = struct + type t = int + + let x = 2 +end + +module R = A.F (S) diff --git a/test/sources/functor.t/root.mld b/test/sources/functor.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/functor.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/functor.t/run.t b/test/sources/functor.t/run.t new file mode 100644 index 0000000000..81017774e1 --- /dev/null +++ b/test/sources/functor.t/run.t @@ -0,0 +1,87 @@ +Verify the behavior on functors. + + $ odoc compile -c module-a -c src-source root.mld + + $ printf "s.ml\na.ml\nb.ml\n" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + $ ocamlc -c -o s.cmo s.ml -bin-annot -I . + $ ocamlc -c -o a.cmo a.ml -bin-annot -I . + $ ocamlc -c -o b.cmo b.ml -bin-annot -I . + $ odoc compile --source-name s.ml --source-parent-file src-source.odoc -I . s.cmt + $ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . a.cmt + $ odoc compile --source-name b.ml --source-parent-file src-source.odoc -I . b.cmt + $ odoc link -I . s.odoc + $ odoc link -I . a.odoc + $ odoc link -I . b.odoc + $ odoc html-generate --source s.ml --indent -o html s.odocl + $ odoc html-generate --source a.ml --indent -o html a.odocl + $ odoc html-generate --source b.ml --indent -o html b.odocl + + $ find html | sort + html + html/A + html/A/F + html/A/F/argument-1-S + html/A/F/argument-1-S/index.html + html/A/F/index.html + html/A/index.html + html/B + html/B/R + html/B/R/index.html + html/B/S + html/B/S/index.html + html/B/index.html + html/S + html/S/index.html + html/S/module-type-S + html/S/module-type-S/index.html + html/root + html/root/source + html/root/source/a.ml.html + html/root/source/b.ml.html + html/root/source/s.ml.html + +In this test, the functor expansion contains the right link. + + $ cat html/A/F/index.html | grep source_link --context=1 +

Module A.F + Source + + -- + + Source + + -- + + Source + + + $ cat html/root/source/a.ml.html | grep L3 + 3 + +However, on functor results, there is a link to source in the file: + + $ cat html/B/R/index.html | grep source_link --context=2 +
+

Module B.R + Source + +

+ -- +
+ + Source + + type t + -- +
+ + Source + + + +Source links in functor parameters might not make sense. Currently we generate none: + + $ cat html/A/F/argument-1-S/index.html | grep source_link --context=1 + [1] diff --git a/test/sources/functor.t/s.ml b/test/sources/functor.t/s.ml new file mode 100644 index 0000000000..a94f22f6ae --- /dev/null +++ b/test/sources/functor.t/s.ml @@ -0,0 +1,4 @@ +module type S = sig + type t + val x : t +end diff --git a/test/sources/include_in_expansion.t/a.ml b/test/sources/include_in_expansion.t/a.ml new file mode 100644 index 0000000000..6964220a83 --- /dev/null +++ b/test/sources/include_in_expansion.t/a.ml @@ -0,0 +1,2 @@ +include B +let x = 1 diff --git a/test/sources/include_in_expansion.t/b.ml b/test/sources/include_in_expansion.t/b.ml new file mode 100644 index 0000000000..cb8642d747 --- /dev/null +++ b/test/sources/include_in_expansion.t/b.ml @@ -0,0 +1 @@ +let y = 1 diff --git a/test/sources/include_in_expansion.t/main.ml b/test/sources/include_in_expansion.t/main.ml new file mode 100644 index 0000000000..4265e8be1b --- /dev/null +++ b/test/sources/include_in_expansion.t/main.ml @@ -0,0 +1,4 @@ +module A = Main__A +(** @canonical Main.A *) + +include B diff --git a/test/sources/include_in_expansion.t/root.mld b/test/sources/include_in_expansion.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/include_in_expansion.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/include_in_expansion.t/run.t b/test/sources/include_in_expansion.t/run.t new file mode 100644 index 0000000000..b9b24291f9 --- /dev/null +++ b/test/sources/include_in_expansion.t/run.t @@ -0,0 +1,36 @@ +Checking that source parents are kept, using include. + + $ odoc compile -c module-a -c src-source root.mld + + $ printf "a.ml\nb.ml\nmain.ml\n" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + $ ocamlc -c -o b.cmo b.ml -bin-annot -I . + $ ocamlc -c -o main__A.cmo a.ml -bin-annot -I . + $ ocamlc -c main.ml -bin-annot -I . + + $ odoc compile --source-name b.ml --source-parent-file src-source.odoc -I . b.cmt + $ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . main__A.cmt + $ odoc compile --source-name main.ml --source-parent-file src-source.odoc -I . main.cmt + + $ odoc link -I . main.odoc + $ odoc link -I . main__A.odoc + + $ odoc html-generate --source main.ml --indent -o html main.odocl + $ odoc html-generate --source a.ml --hidden --indent -o html main__A.odocl + +In Main.A, the source parent of value x should be to Main__A, while the +source parent of value y should be left to B. + + $ grep source_link html/Main/A/index.html -C 1 +

Module Main.A + Source +

+ -- + + Source + val y : int + -- + + Source + val x : int diff --git a/test/sources/lookup_def.t/a.ml b/test/sources/lookup_def.t/a.ml new file mode 100644 index 0000000000..fac2b148aa --- /dev/null +++ b/test/sources/lookup_def.t/a.ml @@ -0,0 +1,28 @@ +module M = struct end + +module N = struct + module type S = sig + val x : int + end + + module T : S = struct + let x = 1 + end +end + +type t + +let a = 2 + +(** Not exported *) +let a' = 3 + +exception Exn + +type ext = .. + +type ext += Ext + +class cls = object end + +class type clst = object end diff --git a/test/sources/lookup_def.t/a.mli b/test/sources/lookup_def.t/a.mli new file mode 100644 index 0000000000..cac4c2306f --- /dev/null +++ b/test/sources/lookup_def.t/a.mli @@ -0,0 +1,23 @@ +module M : sig end + +module N : sig + module type S = sig + val x : int + end + + module T : S +end + +type t + +val a : int + +exception Exn + +type ext = .. + +type ext += Ext + +class cls : object end + +class type clst = object end diff --git a/test/sources/lookup_def.t/root.mld b/test/sources/lookup_def.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/lookup_def.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/lookup_def.t/run.t b/test/sources/lookup_def.t/run.t new file mode 100644 index 0000000000..b17b766cf1 --- /dev/null +++ b/test/sources/lookup_def.t/run.t @@ -0,0 +1,27 @@ +Compile the modules: + + $ odoc compile -c module-a -c src-source root.mld + + $ printf "a.ml\n" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + $ ocamlc -c a.mli a.ml -bin-annot + $ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . a.cmti + $ odoc link a.odoc + +Show the locations: + + $ odoc_print a.odocl | jq -c '.. | select(.locs?) | [ .id, .locs ]' + [{"`Module":[{"`Root":["None","A"]},"M"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-0"}}}] + [{"`Module":[{"`Root":["None","A"]},"N"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-5"}}}] + [{"`ModuleType":[{"`Module":[{"`Root":["None","A"]},"N"]},"S"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-2"}}}] + [{"`Value":[{"`ModuleType":[{"`Module":[{"`Root":["None","A"]},"N"]},"S"]},"x"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-2"}}}] + [{"`Module":[{"`Module":[{"`Root":["None","A"]},"N"]},"T"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-4"}}}] + [{"`Value":[{"`Module":[{"`Module":[{"`Root":["None","A"]},"N"]},"T"]},"x"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-3"}}}] + [{"`Type":[{"`Root":["None","A"]},"t"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-6"}}}] + [{"`Value":[{"`Root":["None","A"]},"a"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-7"}}}] + [{"`Exception":[{"`Root":["None","A"]},"Exn"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-9"}}}] + [{"`Type":[{"`Root":["None","A"]},"ext"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-10"}}}] + [{"`Extension":[{"`Root":["None","A"]},"Ext"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-11"}}}] + [{"`Class":[{"`Root":["None","A"]},"cls"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-12"}}}] + [{"`ClassType":[{"`Root":["None","A"]},"clst"]},{"Some":{"source_parent":[{"`SourceRoot":{"`Page":[{"Some":{"`Page":["None","root"]}},"source"]}},"a.ml"],"anchor":{"Some":"def-14"}}}] diff --git a/test/sources/lookup_def_wrapped.t/a.ml b/test/sources/lookup_def_wrapped.t/a.ml new file mode 100644 index 0000000000..0547b3d0ee --- /dev/null +++ b/test/sources/lookup_def_wrapped.t/a.ml @@ -0,0 +1 @@ +let x = 1 diff --git a/test/sources/lookup_def_wrapped.t/b.ml b/test/sources/lookup_def_wrapped.t/b.ml new file mode 100644 index 0000000000..d28e8d46b9 --- /dev/null +++ b/test/sources/lookup_def_wrapped.t/b.ml @@ -0,0 +1 @@ +let x = Main__A.x diff --git a/test/sources/lookup_def_wrapped.t/main.ml b/test/sources/lookup_def_wrapped.t/main.ml new file mode 100644 index 0000000000..09861952b7 --- /dev/null +++ b/test/sources/lookup_def_wrapped.t/main.ml @@ -0,0 +1,5 @@ +module A = Main__A +(** @canonical Main.A *) + +module B = Main__B +(** @canonical Main.B *) diff --git a/test/sources/lookup_def_wrapped.t/root.mld b/test/sources/lookup_def_wrapped.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/lookup_def_wrapped.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/lookup_def_wrapped.t/run.t b/test/sources/lookup_def_wrapped.t/run.t new file mode 100644 index 0000000000..7a49227923 --- /dev/null +++ b/test/sources/lookup_def_wrapped.t/run.t @@ -0,0 +1,71 @@ +Make sure wrapped libraries don't interfere with generating the source code. +Test both canonical paths and hidden units. +It's a simpler case than Dune's wrapping. + + $ odoc compile -c module-main -c src-source root.mld + + $ printf "a.ml\nb.ml\nmain.ml\n" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + $ ocamlc -c -o main__A.cmo a.ml -bin-annot -I . + $ ocamlc -c -o main__B.cmo b.ml -bin-annot -I . + $ ocamlc -c main.ml -bin-annot -I . + + $ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . main__A.cmt + $ odoc compile --source-name b.ml --source-parent-file src-source.odoc -I . main__B.cmt + $ odoc compile --source-name main.ml --source-parent-file src-source.odoc -I . main.cmt + + $ odoc link -I . main__A.odoc + $ odoc link -I . main__B.odoc + $ odoc link -I . main.odoc + + $ odoc html-generate --source main.ml --indent -o html main.odocl + $ odoc html-generate --source a.ml --hidden --indent -o html main__A.odocl + $ odoc html-generate --source b.ml --hidden --indent -o html main__B.odocl + +Look if all the source files are generated: + + $ find html | sort + html + html/Main + html/Main/A + html/Main/A/index.html + html/Main/B + html/Main/B/index.html + html/Main/index.html + html/root + html/root/source + html/root/source/a.ml.html + html/root/source/b.ml.html + html/root/source/main.ml.html + + $ cat html/Main/A/index.html + + + A (Main.A) + + + + + + + + +
+

Module Main.A + Source +

+
+
+
+
+ + Source + val x : int +
+
+
+ + diff --git a/test/sources/recursive_module.t/main.ml b/test/sources/recursive_module.t/main.ml new file mode 100644 index 0000000000..ab98f09daa --- /dev/null +++ b/test/sources/recursive_module.t/main.ml @@ -0,0 +1,9 @@ +module rec A : sig + type t = B.t +end = + A + +and B : sig + type t = Cons of A.t +end = + B diff --git a/test/sources/recursive_module.t/root.mld b/test/sources/recursive_module.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/recursive_module.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/recursive_module.t/run.t b/test/sources/recursive_module.t/run.t new file mode 100644 index 0000000000..a062233636 --- /dev/null +++ b/test/sources/recursive_module.t/run.t @@ -0,0 +1,27 @@ +Checking that source links exists inside recursive modules. + + $ odoc compile -c module-main -c src-source root.mld + + $ printf "main.ml" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + $ ocamlc -c main.ml -bin-annot -I . + $ odoc compile --source-name main.ml --source-parent-file src-source.odoc -I . main.cmt + $ odoc link -I . main.odoc + $ odoc html-generate --source main.ml --indent -o html main.odocl + +Both modules should contain source links + + $ grep source_link html/Main/A/index.html -C 2 +
+

Module Main.A + Source + +

+ + $ grep source_link html/Main/B/index.html -C 2 +
+

Module Main.B + Source + +

diff --git a/test/sources/single_mli.t/a.ml b/test/sources/single_mli.t/a.ml new file mode 100644 index 0000000000..3f63646446 --- /dev/null +++ b/test/sources/single_mli.t/a.ml @@ -0,0 +1 @@ +module X = A_x diff --git a/test/sources/single_mli.t/a.mli b/test/sources/single_mli.t/a.mli new file mode 100644 index 0000000000..578f820f47 --- /dev/null +++ b/test/sources/single_mli.t/a.mli @@ -0,0 +1,5 @@ +module X : sig + module Y : sig + val z : int +end +end diff --git a/test/sources/single_mli.t/a_x.ml b/test/sources/single_mli.t/a_x.ml new file mode 100644 index 0000000000..00f954d8db --- /dev/null +++ b/test/sources/single_mli.t/a_x.ml @@ -0,0 +1,3 @@ +module Y = struct +let z = 1 + end diff --git a/test/sources/single_mli.t/root.mld b/test/sources/single_mli.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/single_mli.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/single_mli.t/run.t b/test/sources/single_mli.t/run.t new file mode 100644 index 0000000000..9ec5fa5f32 --- /dev/null +++ b/test/sources/single_mli.t/run.t @@ -0,0 +1,68 @@ +Similar to Astring library. + + $ odoc compile -c module-a -c src-source root.mld + + $ printf "a.ml\na_x.ml\n" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + $ ocamlc -c -o a_x.cmo a_x.ml -bin-annot -I . + $ ocamlc -c a.mli -bin-annot -I . + $ ocamlc -c a.ml -bin-annot -I . + + $ odoc compile --hidden --source-name a_x.ml --source-parent-file src-source.odoc -I . a_x.cmt + $ odoc compile --source-name a.ml --source-parent-file src-source.odoc -I . a.cmti + + $ odoc link -I . a_x.odoc + $ odoc link -I . a.odoc + +TODO: It seems that --hidden do not work: + $ odoc_print a_x.odoc | grep hidden + "hidden": "false", + "hidden": "false" + $ odoc_print a_x.odocl | grep hidden + "hidden": "false", + + $ odoc html-generate --source a_x.ml --indent -o html a_x.odocl + $ odoc html-generate --source a.ml --indent -o html a.odocl + +Look if all the source files are generated: + + $ find html | sort + html + html/A + html/A/X + html/A/X/Y + html/A/X/Y/index.html + html/A/X/index.html + html/A/index.html + html/A_x + html/A_x/index.html + html/root + html/root/source + html/root/source/a.ml.html + html/root/source/a_x.ml.html + +Documentation for `A_x` is not generated for hidden modules, but --hidden do not +work right now: + + $ ! [ -f html/A_x/index.html ] + [1] + +Code source for `A_x` is wanted: + + $ [ -f html/root/source/a_x.ml.html ] + +`A` should contain a link to `A_x.ml.html`: + + $ grep source_link html/A/index.html + Source + Source + +`A.X` and `A.X.Y` should contain a link to `A_x.ml.html`: + + $ grep source_link html/A/X/index.html + Source + Source + $ grep source_link html/A/X/Y/index.html + + diff --git a/test/sources/source.t/a.ml b/test/sources/source.t/a.ml new file mode 100644 index 0000000000..abfd6af152 --- /dev/null +++ b/test/sources/source.t/a.ml @@ -0,0 +1,20 @@ +type t = string + +let x = 2 +let y = x + 1 +let z a = if x = 1 || true then x + y else 0 + +module A = struct end +module B = A + +module type T = sig end +module type U = T + +type ext = .. +type ext += Foo + +exception Exn + +class cls = object end +class cls' = cls +class type ct = object end diff --git a/test/sources/source.t/root.mld b/test/sources/source.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/source.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/source.t/run.t b/test/sources/source.t/run.t new file mode 100644 index 0000000000..52e002087a --- /dev/null +++ b/test/sources/source.t/run.t @@ -0,0 +1,155 @@ +Files containing some values: + + $ cat a.ml + type t = string + + let x = 2 + let y = x + 1 + let z a = if x = 1 || true then x + y else 0 + + module A = struct end + module B = A + + module type T = sig end + module type U = T + + type ext = .. + type ext += Foo + + exception Exn + + class cls = object end + class cls' = cls + class type ct = object end + +Source pages require a parent: + + $ odoc compile -c module-a -c src-source root.mld + +Compile the modules: + + $ ocamlc -c a.ml -bin-annot + +Compile the pages without --source: + + $ odoc compile a.cmt + $ odoc link -I . a.odoc + $ odoc html-generate --indent -o html a.odocl + +No source links are generated in the documentation: + + $ ! grep source_link html/A/index.html -B 2 + +Now, compile the pages with the --source option: + + $ printf "a.ml\n" > source_tree.map + $ odoc source-tree -I . --parent page-root -o src-source.odoc source_tree.map + + $ odoc compile -I . --source-name a.ml --source-parent-file src-source.odoc a.cmt + $ odoc link -I . a.odoc + $ odoc html-generate --source a.ml --indent -o html a.odocl + +Source links generated in the documentation: + + $ grep source_link html/A/index.html -B 2 +
+

Module A + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + -- +
+ + Source + +Ids generated in the source code: + + $ cat html/root/source/a.ml.html | tr '> ' '\n\n' | grep '^id' + id="L1" + id="L2" + id="L3" + id="L4" + id="L5" + id="L6" + id="L7" + id="L8" + id="L9" + id="L10" + id="L11" + id="L12" + id="L13" + id="L14" + id="L15" + id="L16" + id="L17" + id="L18" + id="L19" + id="L20" + id="def-0" + id="def-1" + id="x_268" + id="def-2" + id="y_269" + id="def-3" + id="z_270" + id="a_272" + id="def-5" + id="def-6" + id="def-7" + id="def-8" + id="def-9" + id="def-10" + id="def-11" + id="def-12" + id="def-14" + id="def-15" diff --git a/test/sources/source_hierarchy.t/a.ml b/test/sources/source_hierarchy.t/a.ml new file mode 100644 index 0000000000..cb8642d747 --- /dev/null +++ b/test/sources/source_hierarchy.t/a.ml @@ -0,0 +1 @@ +let y = 1 diff --git a/test/sources/source_hierarchy.t/b.ml b/test/sources/source_hierarchy.t/b.ml new file mode 100644 index 0000000000..b6a2459810 --- /dev/null +++ b/test/sources/source_hierarchy.t/b.ml @@ -0,0 +1 @@ +let x = 0 diff --git a/test/sources/source_hierarchy.t/c.ml b/test/sources/source_hierarchy.t/c.ml new file mode 100644 index 0000000000..8a76a984f9 --- /dev/null +++ b/test/sources/source_hierarchy.t/c.ml @@ -0,0 +1 @@ +let w = 5 diff --git a/test/sources/source_hierarchy.t/root.mld b/test/sources/source_hierarchy.t/root.mld new file mode 100644 index 0000000000..54f377d3e8 --- /dev/null +++ b/test/sources/source_hierarchy.t/root.mld @@ -0,0 +1 @@ +{0 Root} diff --git a/test/sources/source_hierarchy.t/run.t b/test/sources/source_hierarchy.t/run.t new file mode 100644 index 0000000000..4e5df76750 --- /dev/null +++ b/test/sources/source_hierarchy.t/run.t @@ -0,0 +1,80 @@ +A page can have source children. + + $ odoc compile -c module-a -c module-b -c src-source root.mld + + $ printf "lib/main.ml\nlib/b/b.ml\nlib/a/a.ml\n" > source.map + $ odoc source-tree -I . --parent page-root source.map + +Compile the modules: + + $ ocamlc -c a.ml -bin-annot + $ ocamlc -c b.ml -bin-annot + $ ocamlc -c c.ml -bin-annot + +Now, compile the pages with the --source option. The source-name must be included in the source-children of the source-parent: + + $ odoc compile -I . --source-name lib/a/a.ml --source-parent-file src-source.odoc a.cmt + $ odoc compile -I . --source-name lib/b/b.ml --source-parent-file src-source.odoc b.cmt + $ odoc compile -I . --source-name lib/main.ml --source-parent-file src-source.odoc c.cmt + $ odoc link -I . page-root.odoc + $ odoc link -I . a.odoc + $ odoc link -I . b.odoc + $ odoc link -I . c.odoc + $ odoc link -I . src-source.odoc + $ odoc html-generate --indent -o html page-root.odocl + $ odoc html-generate --indent -o html src-source.odocl + $ odoc html-generate --source a.ml --indent -o html a.odocl + $ odoc html-generate --source b.ml --indent -o html b.odocl + $ odoc html-generate --source c.ml --indent -o html c.odocl + +Source pages and source directory pages are generated: + + $ find html | sort + html + html/A + html/A/index.html + html/B + html/B/index.html + html/C + html/C/index.html + html/root + html/root/index.html + html/root/source + html/root/source/index.html + html/root/source/lib + html/root/source/lib/a + html/root/source/lib/a/a.ml.html + html/root/source/lib/a/index.html + html/root/source/lib/b + html/root/source/lib/b/b.ml.html + html/root/source/lib/b/index.html + html/root/source/lib/index.html + html/root/source/lib/main.ml.html + +A directory simply list its children: + + $ cat html/root/source/lib/index.html + + + lib (root.source.lib) + + + + + + + +
+

./lib/

+ +
+ + diff --git a/test/xref2/canonical_nested.t/run.t b/test/xref2/canonical_nested.t/run.t index 74eebe9c3a..fe11c2181f 100644 --- a/test/xref2/canonical_nested.t/run.t +++ b/test/xref2/canonical_nested.t/run.t @@ -44,6 +44,7 @@ unresolved in the paths though: "B" ] }, + "locs": "None", "doc": [], "type_": { "Alias": [ @@ -87,6 +88,7 @@ unresolved in the paths though: $ odoc_print -r Container main.odoc { "id": { "`Module": [ { "`Root": [ "None", "Main" ] }, "Container" ] }, + "locs": "None", "doc": [], "type_": { "Alias": [ @@ -129,6 +131,7 @@ unresolved in the paths though: "B" ] }, + "locs": "None", "doc": [], "type_": { "Alias": [ @@ -205,6 +208,7 @@ unresolved in the paths though: "t" ] }, + "locs": "None", "doc": [], "equation": { "params": [], diff --git a/test/xref2/classes.t/run.t b/test/xref2/classes.t/run.t index 318b85c8cb..761bdd80f3 100644 --- a/test/xref2/classes.t/run.t +++ b/test/xref2/classes.t/run.t @@ -16,6 +16,7 @@ resolve correctly. All of the 'Class' json objects should contain $ odoc_print -r f f.odoc { "id": { "`Value": [ { "`Root": [ "None", "F" ] }, "f" ] }, + "locs": "None", "doc": [], "type_": { "Class": [ @@ -34,6 +35,7 @@ resolve correctly. All of the 'Class' json objects should contain $ odoc_print e.odoc -r g { "id": { "`Value": [ { "`Root": [ "None", "E" ] }, "g" ] }, + "locs": "None", "doc": [], "type_": { "Class": [ @@ -72,34 +74,42 @@ resolve correctly. All of the 'Class' json objects should contain ] } - $ odoc_print c.odoc -r g + $ odoc_print c.odoc -r g | jq '.type_' { - "id": { "`Value": [ { "`Root": [ "None", "C" ] }, "g" ] }, - "doc": [], - "type_": { - "Arrow": [ - "None", - { - "Class": [ - { - "`Resolved": { - "`ClassType": [ - { "`Identifier": { "`Root": [ "None", "B" ] } }, - "u" - ] + "Arrow": [ + "None", + { + "Class": [ + { + "`Resolved": { + "`ClassType": [ + { + "`Identifier": { + "`Root": [ + "None", + "B" + ] + } + }, + "u" + ] + } + }, + [] + ] + }, + { + "Constr": [ + { + "`Resolved": { + "`Identifier": { + "`CoreType": "unit" } - }, - [] - ] - }, - { - "Constr": [ - { "`Resolved": { "`Identifier": { "`CoreType": "unit" } } }, - [] - ] - } - ] - }, - "value": "Abstract" + } + }, + [] + ] + } + ] } diff --git a/test/xref2/deep_substitution.t/run.t b/test/xref2/deep_substitution.t/run.t index ad330fed65..17651deb07 100644 --- a/test/xref2/deep_substitution.t/run.t +++ b/test/xref2/deep_substitution.t/run.t @@ -27,6 +27,7 @@ its RHS correctly replaced with an `int` "t" ] }, + "locs": "None", "doc": [], "equation": { "params": [], diff --git a/test/xref2/dune b/test/xref2/dune index 3525c38641..c742295f83 100644 --- a/test/xref2/dune +++ b/test/xref2/dune @@ -32,3 +32,10 @@ (applies_to github_issue_793) (enabled_if (>= %{ocaml_version} 4.13.0))) + +; 4.14.0 and above + +(cram + (applies_to lookup_def) + (enabled_if + (>= %{ocaml_version} 4.14.0))) diff --git a/test/xref2/lib/common.cppo.ml b/test/xref2/lib/common.cppo.ml index bc5b878b44..08c0a710e1 100644 --- a/test/xref2/lib/common.cppo.ml +++ b/test/xref2/lib/common.cppo.ml @@ -615,6 +615,7 @@ let my_compilation_unit id (s : Odoc_model.Lang.Signature.t) = ; expansion = None ; linked = false ; canonical = None + ; source_info = None } let mkresolver () = @@ -638,7 +639,7 @@ let handle_warnings ww = let resolve unit = let resolver = mkresolver () in - let resolve_env = Odoc_odoc.Resolver.build_env_for_unit resolver ~linking:true unit in + let resolve_env = Odoc_odoc.Resolver.build_compile_env_for_unit resolver None unit in Odoc_xref2.Compile.compile ~filename:"" resolve_env unit |> handle_warnings diff --git a/test/xref2/module_preamble.t/run.t b/test/xref2/module_preamble.t/run.t index d4d3822a74..0e7895eec0 100644 --- a/test/xref2/module_preamble.t/run.t +++ b/test/xref2/module_preamble.t/run.t @@ -26,7 +26,6 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered html/test/A/index.html html/test/A/B/index.html $ odoc html-targets -o html a__b.odocl - html/test/A__b/index.html $ cat html/test/A/index.html @@ -106,22 +105,5 @@ and that "hidden" modules (eg. `A__b`, rendered to `html/A__b`) are not rendered `A__b` shouldn't render: - $ cat html/test/A__b/index.html - - - A__b (test.A__b) - - - - - - - - -
-

Module A__b

-
- - + $ ! cat html/test/A__b/index.html + cat: html/test/A__b/index.html: No such file or directory diff --git a/test/xref2/resolve/test.md b/test/xref2/resolve/test.md index 83b713964c..ba8df513bf 100644 --- a/test/xref2/resolve/test.md +++ b/test/xref2/resolve/test.md @@ -101,7 +101,7 @@ Simplest possible resolution: ihash = 818126955; ikey = "r_Root.p_None"}, t); ihash = 1016576344; ikey = "t_t.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -119,7 +119,7 @@ Simplest possible resolution: ihash = 818126955; ikey = "r_Root.p_None"}, u); ihash = 15973539; ikey = "t_u.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = @@ -143,7 +143,7 @@ Simplest possible resolution: constraints = []}; representation = None})]; compiled = true; doc = []}; - expansion = None; linked = false; canonical = None} + expansion = None; linked = false; canonical = None; source_info = None} ``` Let's look at a marginally more complicated example. In this case, our type `t` @@ -246,7 +246,7 @@ Basic resolution 2, environment lookup: ihash = 818126955; ikey = "r_Root.p_None"}, M); ihash = 716453475; ikey = "m_M.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature @@ -270,7 +270,7 @@ Basic resolution 2, environment lookup: ihash = 716453475; ikey = "m_M.r_Root.p_None"}, t); ihash = 746522241; ikey = "t_t.m_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -290,7 +290,7 @@ Basic resolution 2, environment lookup: ihash = 818126955; ikey = "r_Root.p_None"}, u); ihash = 15973539; ikey = "t_u.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = @@ -316,7 +316,7 @@ Basic resolution 2, environment lookup: constraints = []}; representation = None})]; compiled = true; doc = []}; - expansion = None; linked = false; canonical = None} + expansion = None; linked = false; canonical = None; source_info = None} ``` @@ -392,7 +392,7 @@ Basic resolution 3, module type: ihash = 818126955; ikey = "r_Root.p_None"}, M); ihash = 459143770; ikey = "mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -416,7 +416,7 @@ Basic resolution 3, module type: ihash = 459143770; ikey = "mt_M.r_Root.p_None"}, t); ihash = 825731485; ikey = "t_t.mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -435,7 +435,7 @@ Basic resolution 3, module type: ihash = 818126955; ikey = "r_Root.p_None"}, N); ihash = 502470005; ikey = "m_N.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Path @@ -462,7 +462,7 @@ Basic resolution 3, module type: ihash = 502470005; ikey = "m_N.r_Root.p_None"}, t); ihash = 598040815; ikey = "t_t.m_N.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -497,7 +497,7 @@ Basic resolution 3, module type: ihash = 818126955; ikey = "r_Root.p_None"}, u); ihash = 15973539; ikey = "t_u.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = @@ -508,22 +508,17 @@ Basic resolution 3, module type: (`Identifier {Odoc_model__Paths_types.iv = `Module - ({Odoc_model__Paths_types.iv = - `Root - (Some - {Odoc_model__Paths_types.iv = `Page ...; - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}, - ...)), - ...)); - constraints = ...}; - representation = ...}); - ...]; - compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + ({Odoc_model__Paths_types.iv = `Root (...); + ihash = ...; ikey = ...}, + ...); + ihash = ...; ikey = ...}, + ...)), + ...)); + constraints = ...}; + representation = ...}); + ...]; + compiled = ...; doc = ...}; + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` This example is very similar but there is one more level of nesting of the modules: @@ -577,7 +572,7 @@ Basic resolution 4, module type: ihash = 818126955; ikey = "r_Root.p_None"}, M); ihash = 459143770; ikey = "mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -601,7 +596,7 @@ Basic resolution 4, module type: ihash = 459143770; ikey = "mt_M.r_Root.p_None"}, N); ihash = 998243332; ikey = "m_N.mt_M.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature @@ -634,7 +629,7 @@ Basic resolution 4, module type: t); ihash = 687003328; ikey = "t_t.m_N.mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; @@ -656,7 +651,7 @@ Basic resolution 4, module type: ihash = 818126955; ikey = "r_Root.p_None"}, A); ihash = 353272258; ikey = "m_A.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Path @@ -683,7 +678,7 @@ Basic resolution 4, module type: ihash = 353272258; ikey = "m_A.r_Root.p_None"}, N); ihash = 456955352; ikey = "m_N.m_A.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature @@ -707,19 +702,15 @@ Basic resolution 4, module type: Root); ihash = 818126955; ikey = - "r_Root."... (* string length 13; truncated *)}, + "r_Root.p"... (* string length 13; truncated *)}, A); - ihash = 353272258; - ikey = - "m_A."... (* string length 17; truncated *)}, - N); - ihash = 456955352; - ikey = - "m"... (* string length 21; truncated *)}, - t); + ihash = 353272258; ikey = ...}, + ...); + ihash = ...; ikey = ...}, + ...); ihash = ...; ikey = ...}; - doc = ...; canonical = ...; equation = ...; - representation = ...}); + locs = ...; doc = ...; canonical = ...; + equation = ...; representation = ...}); ...]; compiled = ...; doc = ...}); canonical = ...; hidden = ...}); @@ -729,7 +720,7 @@ Basic resolution 4, module type: canonical = ...; hidden = ...}); ...]; compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` This example is rather more interesting: @@ -819,7 +810,7 @@ and then we can look up the type `t`. ihash = 818126955; ikey = "r_Root.p_None"}, M); ihash = 459143770; ikey = "mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -842,7 +833,7 @@ and then we can look up the type `t`. ihash = 459143770; ikey = "mt_M.r_Root.p_None"}, N); ihash = 887387323; ikey = "mt_N.mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -875,7 +866,7 @@ and then we can look up the type `t`. t); ihash = 652783314; ikey = "t_t.mt_N.mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; @@ -901,7 +892,7 @@ and then we can look up the type `t`. ihash = 459143770; ikey = "mt_M.r_Root.p_None"}, B); ihash = 301928208; ikey = "m_B.mt_M.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Path @@ -937,7 +928,7 @@ and then we can look up the type `t`. t); ihash = 484865120; ikey = "t_t.m_B.mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; @@ -953,23 +944,18 @@ and then we can look up the type `t`. ({Odoc_model__Paths_types.iv = `ModuleType ({Odoc_model__Paths_types.iv = - `Root - (Some - {Odoc_model__Paths_types.iv = - `Page (...); - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...})}); - canonical = ...; hidden = ...}); - ...]; - compiled = ...; doc = ...})}; - ...]; - compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + `Root (Some ...); ihash = ...; + ikey = ...}, + ...); + ihash = ...; ikey = ...}, + ...); + ihash = ...; ikey = ...})}); + canonical = ...; hidden = ...}); + ...]; + compiled = ...; doc = ...})}; + ...]; + compiled = ...; doc = ...}; + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` ```ocaml @@ -1012,7 +998,7 @@ and then we can look up the type `t`. ihash = 818126955; ikey = "r_Root.p_None"}, M); ihash = 459143770; ikey = "mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -1035,7 +1021,7 @@ and then we can look up the type `t`. ihash = 459143770; ikey = "mt_M.r_Root.p_None"}, N); ihash = 887387323; ikey = "mt_N.mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -1068,7 +1054,7 @@ and then we can look up the type `t`. t); ihash = 652783314; ikey = "t_t.mt_N.mt_M.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; @@ -1094,7 +1080,7 @@ and then we can look up the type `t`. ihash = 459143770; ikey = "mt_M.r_Root.p_None"}, X); ihash = 573009176; ikey = "m_X.mt_M.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature @@ -1127,7 +1113,7 @@ and then we can look up the type `t`. B); ihash = 413241446; ikey = "m_B.m_X.mt_M.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Path @@ -1149,41 +1135,33 @@ and then we can look up the type `t`. = `ModuleType ({Odoc_model__Paths_types.iv - = - `Root - (Some - {Odoc_model__Paths_types.iv - = ...; - ihash = - ...; - ikey = - ...}, - ...); - ihash = ...; - ikey = ...}, - ...); - ihash = ...; - ikey = ...}, - ...); - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}; - doc = ...; canonical = ...; - equation = ...; representation = ...}); - ...]; - compiled = ...; doc = ...}); - p_path = ...}); - canonical = ...; hidden = ...}); - ...]; - compiled = ...; doc = ...}); - canonical = ...; hidden = ...}); - ...]; - compiled = ...; doc = ...})}; - ...]; - compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + = `Root ...; + ihash = ...; + ikey = ...}, + ...); + ihash = ...; + ikey = ...}, + ...); + ihash = ...; ikey = ...}, + ...); + ihash = ...; ikey = ...}, + ...); + ihash = ...; ikey = ...}; + locs = ...; doc = ...; + canonical = ...; equation = ...; + representation = ...}); + ...]; + compiled = ...; doc = ...}); + p_path = ...}); + canonical = ...; hidden = ...}); + ...]; + compiled = ...; doc = ...}); + canonical = ...; hidden = ...}); + ...]; + compiled = ...; doc = ...})}; + ...]; + compiled = ...; doc = ...}; + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` Ensure a substitution is taken into account during resolution: @@ -1228,7 +1206,7 @@ Ensure a substitution is taken into account during resolution: ihash = 818126955; ikey = "r_Root.p_None"}, A); ihash = 231492881; ikey = "mt_A.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -1252,7 +1230,7 @@ Ensure a substitution is taken into account during resolution: ihash = 231492881; ikey = "mt_A.r_Root.p_None"}, M); ihash = 564635453; ikey = "m_M.mt_A.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature @@ -1284,7 +1262,8 @@ Ensure a substitution is taken into account during resolution: S); ihash = 3092406; ikey = "mt_S.m_M.mt_A.r_Root.p_None"}; - doc = []; canonical = None; expr = None}]; + locs = None; doc = []; canonical = None; + expr = None}]; compiled = true; doc = []}); canonical = None; hidden = false}); Odoc_model.Lang.Signature.Module @@ -1306,7 +1285,7 @@ Ensure a substitution is taken into account during resolution: ihash = 231492881; ikey = "mt_A.r_Root.p_None"}, N); ihash = 50158313; ikey = "m_N.mt_A.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Path @@ -1349,25 +1328,22 @@ Ensure a substitution is taken into account during resolution: {Odoc_model__Paths_types.iv = `Page (None, None); ihash = 236059787; ikey = "p_None"}, Root); - ihash = 818126955; ikey = "r_Root.p_None"}, + ihash = 818126955; + ikey = "r_Root.p_No"... (* string length 13; truncated *)}, B); ihash = 814134997; - ikey = "m_B.r_Root.p"... (* string length 17; truncated *)}; - doc = []; + ikey = "m_B.r_Ro"... (* string length 17; truncated *)}; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature {Odoc_model.Lang.Signature.items = - [Odoc_model.Lang.Signature.ModuleType - {Odoc_model.Lang.ModuleType.id = - {Odoc_model__Paths_types.iv = ...; ihash = ...; ikey = ...}; - doc = ...; canonical = ...; expr = ...}; - ...]; - compiled = ...; doc = ...}); - canonical = ...; hidden = ...}); - ...]; - compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + [Odoc_model.Lang.Signature.ModuleType ...]; compiled = ...; + doc = ...}); + canonical = ...; hidden = ...}); + ...]; + compiled = ...; doc = ...}; + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` Ensure a destructive substitution is taken into account during resolution: @@ -1412,7 +1388,7 @@ Ensure a destructive substitution is taken into account during resolution: ihash = 818126955; ikey = "r_Root.p_None"}, A); ihash = 231492881; ikey = "mt_A.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -1436,7 +1412,7 @@ Ensure a destructive substitution is taken into account during resolution: ihash = 231492881; ikey = "mt_A.r_Root.p_None"}, M); ihash = 564635453; ikey = "m_M.mt_A.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature @@ -1468,7 +1444,8 @@ Ensure a destructive substitution is taken into account during resolution: S); ihash = 3092406; ikey = "mt_S.m_M.mt_A.r_Root.p_None"}; - doc = []; canonical = None; expr = None}]; + locs = None; doc = []; canonical = None; + expr = None}]; compiled = true; doc = []}); canonical = None; hidden = false}); Odoc_model.Lang.Signature.Module @@ -1490,7 +1467,7 @@ Ensure a destructive substitution is taken into account during resolution: ihash = 231492881; ikey = "mt_A.r_Root.p_None"}, N); ihash = 50158313; ikey = "m_N.mt_A.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Path @@ -1533,25 +1510,22 @@ Ensure a destructive substitution is taken into account during resolution: {Odoc_model__Paths_types.iv = `Page (None, None); ihash = 236059787; ikey = "p_None"}, Root); - ihash = 818126955; ikey = "r_Root.p_None"}, + ihash = 818126955; + ikey = "r_Root.p_No"... (* string length 13; truncated *)}, B); ihash = 814134997; - ikey = "m_B.r_Root.p"... (* string length 17; truncated *)}; - doc = []; + ikey = "m_B.r_Ro"... (* string length 17; truncated *)}; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature {Odoc_model.Lang.Signature.items = - [Odoc_model.Lang.Signature.ModuleType - {Odoc_model.Lang.ModuleType.id = - {Odoc_model__Paths_types.iv = ...; ihash = ...; ikey = ...}; - doc = ...; canonical = ...; expr = ...}; - ...]; - compiled = ...; doc = ...}); - canonical = ...; hidden = ...}); - ...]; - compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + [Odoc_model.Lang.Signature.ModuleType ...]; compiled = ...; + doc = ...}); + canonical = ...; hidden = ...}); + ...]; + compiled = ...; doc = ...}; + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` Resolve a module alias: @@ -1591,7 +1565,7 @@ Resolve a module alias: ihash = 818126955; ikey = "r_Root.p_None"}, A); ihash = 353272258; ikey = "m_A.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature @@ -1615,7 +1589,7 @@ Resolve a module alias: ihash = 353272258; ikey = "m_A.r_Root.p_None"}, t); ihash = 394964294; ikey = "t_t.m_A.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -1635,7 +1609,7 @@ Resolve a module alias: ihash = 818126955; ikey = "r_Root.p_None"}, B); ihash = 814134997; ikey = "m_B.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.Alias (`Resolved @@ -1666,7 +1640,7 @@ Resolve a module alias: ihash = 818126955; ikey = "r_Root.p_None"}, t); ihash = 1016576344; ikey = "t_t.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = @@ -1698,18 +1672,20 @@ Resolve a module alias: `Page (None, None); ihash = 236059787; ikey = "p_None"}, Root); - ihash = 818126955; ikey = "r_Root.p_None"}, + ihash = 818126955; + ikey = + "r_Root.p_"... (* string length 13; truncated *)}, B); ihash = 814134997; ikey = - "m_B.r_Root"... (* string length 17; truncated *)}, + "m_B.r_Ro"... (* string length 17; truncated *)}, false)), t)), [])); constraints = []}; representation = None})]; - compiled = true; doc = []}; - expansion = None; linked = false; canonical = ...} + compiled = true; doc = ...}; + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` Resolve a module alias: @@ -1750,7 +1726,7 @@ Resolve a module alias: ihash = 818126955; ikey = "r_Root.p_None"}, A); ihash = 353272258; ikey = "m_A.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Signature @@ -1774,7 +1750,7 @@ Resolve a module alias: ihash = 353272258; ikey = "m_A.r_Root.p_None"}, t); ihash = 394964294; ikey = "t_t.m_A.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -1794,7 +1770,7 @@ Resolve a module alias: ihash = 818126955; ikey = "r_Root.p_None"}, B); ihash = 814134997; ikey = "m_B.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.Alias (`Resolved @@ -1825,7 +1801,7 @@ Resolve a module alias: ihash = 818126955; ikey = "r_Root.p_None"}, C); ihash = 43786577; ikey = "m_C.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.Alias (`Resolved @@ -1855,22 +1831,20 @@ Resolve a module alias: Root); ihash = 818126955; ikey = "r_Root.p_None"}, B); - ihash = 814134997; ikey = "m_B.r_Root.p_None"}, + ihash = 814134997; + ikey = + "m_B.r_Root.p_"... (* string length 17; truncated *)}, false))), None); canonical = None; hidden = false}); Odoc_model.Lang.Signature.Type (Odoc_model.Lang.Signature.Ordinary, {Odoc_model.Lang.TypeDecl.id = - {Odoc_model__Paths_types.iv = - `Type - ({Odoc_model__Paths_types.iv = `Root ...; ihash = ...; - ikey = ...}, - ...); - ihash = ...; ikey = ...}; - doc = ...; canonical = ...; equation = ...; representation = ...}); - ...]; - compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + {Odoc_model__Paths_types.iv = `Type (...); ihash = ...; ikey = ...}; + locs = ...; doc = ...; canonical = ...; equation = ...; + representation = ...}); + ...]; + compiled = ...; doc = ...}; + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` Resolve a functor: @@ -1914,7 +1888,7 @@ Resolve a functor: ihash = 818126955; ikey = "r_Root.p_None"}, S); ihash = 527535255; ikey = "mt_S.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -1938,7 +1912,7 @@ Resolve a functor: ihash = 527535255; ikey = "mt_S.r_Root.p_None"}, t); ihash = 130637260; ikey = "t_t.mt_S.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -1957,7 +1931,7 @@ Resolve a functor: ihash = 818126955; ikey = "r_Root.p_None"}, F); ihash = 748202139; ikey = "m_F.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Functor @@ -2013,7 +1987,7 @@ Resolve a functor: t); ihash = 1065278958; ikey = "t_t.p_X.m_F.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; @@ -2036,17 +2010,14 @@ Resolve a functor: S); ihash = 527535255; ikey = - "mt_S.r_Root.p_Non"... (* string length 18; truncated *)})}}, + "mt_S.r_Root.p"... (* string length 18; truncated *)})}}, Odoc_model.Lang.ModuleType.Functor (Odoc_model.Lang.FunctorParameter.Named {Odoc_model.Lang.FunctorParameter.id = {Odoc_model__Paths_types.iv = `Parameter - ({Odoc_model__Paths_types.iv = - `Result - {Odoc_model__Paths_types.iv = `Module ...; - ihash = ...; ikey = ...}; - ihash = ...; ikey = ...}, + ({Odoc_model__Paths_types.iv = `Result ...; ihash = ...; + ikey = ...}, ...); ihash = ...; ikey = ...}; expr = ...}, @@ -2054,7 +2025,7 @@ Resolve a functor: canonical = ...; hidden = ...}); ...]; compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` Resolve a functor: @@ -2120,7 +2091,7 @@ Resolve a functor: ihash = 818126955; ikey = "r_Root.p_None"}, S); ihash = 527535255; ikey = "mt_S.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -2144,7 +2115,7 @@ Resolve a functor: ihash = 527535255; ikey = "mt_S.r_Root.p_None"}, t); ihash = 130637260; ikey = "t_t.mt_S.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; constraints = []}; @@ -2163,7 +2134,7 @@ Resolve a functor: ihash = 818126955; ikey = "r_Root.p_None"}, S1); ihash = 289200525; ikey = "mt_S1.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Functor @@ -2219,7 +2190,7 @@ Resolve a functor: t); ihash = 993900890; ikey = "t_t.p__.mt_S1.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; equation = {Odoc_model.Lang.TypeDecl.Equation.params = []; private_ = false; manifest = None; @@ -2242,7 +2213,7 @@ Resolve a functor: S); ihash = 527535255; ikey = - "mt_S.r_Root.p_Non"... (* string length 18; truncated *)})}}, + "mt_S.r_Root.p"... (* string length 18; truncated *)})}}, Odoc_model.Lang.ModuleType.Path {Odoc_model.Lang.ModuleType.p_expansion = Some @@ -2251,20 +2222,16 @@ Resolve a functor: [Odoc_model.Lang.Signature.Type (Odoc_model.Lang.Signature.Ordinary, {Odoc_model.Lang.TypeDecl.id = - {Odoc_model__Paths_types.iv = - `Type - ({Odoc_model__Paths_types.iv = ...; ihash = ...; - ikey = ...}, - ...); - ihash = ...; ikey = ...}; - doc = ...; canonical = ...; equation = ...; - representation = ...}); + {Odoc_model__Paths_types.iv = ...; ihash = ...; + ikey = ...}; + locs = ...; doc = ...; canonical = ...; + equation = ...; representation = ...}); ...]; compiled = ...; doc = ...}); p_path = ...}))}; ...]; compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + expansion = ...; linked = ...; canonical = ...; source_info = ...} ``` ```ocaml skip @@ -2348,7 +2315,7 @@ Functor app nightmare: ihash = 818126955; ikey = "r_Root.p_None"}, Type); ihash = 359972898; ikey = "mt_Type.r_Root.p_None"}; - doc = []; canonical = None; + locs = None; doc = []; canonical = None; expr = Some (Odoc_model.Lang.ModuleType.Signature @@ -2371,7 +2338,7 @@ Functor app nightmare: ihash = 359972898; ikey = "mt_Type.r_Root.p_None"}, T); ihash = 1011869183; ikey = "mt_T.mt_Type.r_Root.p_None"}; - doc = []; canonical = None; expr = None}]; + locs = None; doc = []; canonical = None; expr = None}]; compiled = true; doc = []})}; Odoc_model.Lang.Signature.Module (Odoc_model.Lang.Signature.Ordinary, {Odoc_model.Lang.Module.id = @@ -2386,7 +2353,7 @@ Functor app nightmare: ihash = 818126955; ikey = "r_Root.p_None"}, App); ihash = 855073208; ikey = "m_App.r_Root.p_None"}; - doc = []; + locs = None; doc = []; type_ = Odoc_model.Lang.Module.ModuleType (Odoc_model.Lang.ModuleType.Functor @@ -2441,7 +2408,8 @@ Functor app nightmare: T); ihash = 167832761; ikey = "mt_T.p_T.m_App.r_Root.p_None"}; - doc = []; canonical = None; expr = None}]; + locs = None; doc = []; canonical = None; + expr = None}]; compiled = true; doc = []}); p_path = `Resolved @@ -2468,22 +2436,16 @@ Functor app nightmare: {Odoc_model__Paths_types.iv = `Module ({Odoc_model__Paths_types.iv = - `Root - (Some - {Odoc_model__Paths_types.iv = - `Page (...); - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}; - ihash = ...; ikey = ...}, - ...); - ihash = ...; ikey = ...}; - expr = ...}, - ...))); - canonical = ...; hidden = ...}); - ...]; - compiled = ...; doc = ...}; - expansion = ...; linked = ...; canonical = ...} + `Root (Some ...); ihash = ...; ikey = ...}, + ...); + ihash = ...; ikey = ...}; + ihash = ...; ikey = ...}, + ...); + ihash = ...; ikey = ...}; + expr = ...}, + ...))); + canonical = ...; hidden = ...}); + ...]; + compiled = ...; doc = ...}; + expansion = ...; linked = ...; canonical = ...; source_info = ...} ```