• Home
  • Features
  • Pricing
  • Docs
  • Announcements
  • Sign In

ocaml / odoc / 2735

15 Jan 2025 05:29PM UTC coverage: 73.399% (-0.07%) from 73.471%
2735

push

github

jonludlam
Update test results

10256 of 13973 relevant lines covered (73.4%)

9962.83 hits per line

Source File
Press 'n' to go to next uncovered line, 'b' for previous

82.16
/src/odoc/resolver.ml
1
(*
2
 * Copyright (c) 2014 Leo White <leo@lpw25.net>
3
 *
4
 * Permission to use, copy, modify, and distribute this software for any
5
 * purpose with or without fee is hereby granted, provided that the above
6
 * copyright notice and this permission notice appear in all copies.
7
 *
8
 * THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
9
 * WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
10
 * MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
11
 * ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
12
 * WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
13
 * ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
14
 * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
15
 *)
16

17
(* We are slightly more flexible here than OCaml usually is, and allow
18
   'linking' of modules that have the same name. This is because we do
19
   documentation at a package level - it's perfectly acceptable to have
20
   libraries within a package that are never meant to be linked into the same
21
   binary, however package-level documents such as module and type indexes
22
   effectively have to link those libraries together. Hence we may find
23
   ourselves in the unfortunate situation where there are multiple modules with the same
24
   name in our include path. We therefore maintain a mapping of module/page
25
   name to Root _list_. Where we've already made a judgement about which module
26
   we're looking for we have a digest, and can pick the correct module. When we
27
   don't (for example, when handling package-level mld files), we pick the
28
   first right now. The ocamldoc syntax doesn't currently allow for specifying
29
   more accurately than just the module name anyway.
30

31
   Where we notice this ambiguity we warn the user to wrap their libraries,
32
   which will generally fix this issue. *)
33

34
open Odoc_utils
35
open Or_error
36

37
type named_root = string * Fs.Directory.t
38
module Named_roots : sig
39
  type t
40

41
  type error = NoPackage | NoRoot
42

43
  type input = { name : string; dir : Fs.Directory.t }
44

45
  val create : input list -> current_root:named_root option -> t
46

47
  val current_root : t -> Fs.Directory.t option
48

49
  val find_by_path :
50
    ?root:string -> t -> path:Fs.File.t -> (Fs.File.t option, error) result
51

52
  val find_by_name :
53
    ?root:string -> t -> name:string -> (Fs.File.t list, error) result
54
end = struct
55
  type flat =
56
    | Unvisited of Fs.Directory.t
57
    | Visited of (string, Fs.File.t) Hashtbl.t
58

59
  type hierarchical = (Fs.File.t, Fs.File.t) Hashtbl.t * Fs.Directory.t
60

61
  type pkg = { flat : flat; hierarchical : hierarchical }
62

63
  type t = { table : (string, pkg) Hashtbl.t; current_root : named_root option }
64

65
  type input = { name : string; dir : Fs.Directory.t }
66

67
  type error = NoPackage | NoRoot
68

69
  let hashtbl_find_opt cache package =
70
    match Hashtbl.find cache package with
181✔
71
    | x -> Some x
77✔
72
    | exception Not_found -> None
104✔
73

74
  let create (pkglist : input list) ~current_root =
75
    let cache = Hashtbl.create 42 in
556✔
76
    List.iter
556✔
77
      (fun { name = pkgname; dir = root } ->
78
        let flat = Unvisited root
77✔
79
        and hierarchical = (Hashtbl.create 42, root) in
77✔
80
        Hashtbl.add cache pkgname { flat; hierarchical })
81
      pkglist;
82
    { current_root; table = cache }
556✔
83

84
  let current_root t = Option.map snd t.current_root
248✔
85

86
  let find_by_path ?root { table = cache; current_root; _ } ~path =
87
    let path = Fpath.normalize path in
142✔
88
    let root =
142✔
89
      match (root, current_root) with
90
      | Some pkg, _ | None, Some (pkg, _) -> Ok pkg
28✔
91
      | None, None -> Error NoRoot
22✔
92
    in
93
    root >>= fun root ->
94
    match hashtbl_find_opt cache root with
120✔
95
    | Some { hierarchical = cache, root; _ } -> (
61✔
96
        match hashtbl_find_opt cache path with
97
        | Some x -> Ok (Some x)
16✔
98
        | None ->
45✔
99
            let full_path = Fpath.( // ) (Fs.Directory.to_fpath root) path in
45✔
100
            if Fs.File.exists full_path then (
29✔
101
              Hashtbl.add cache path full_path;
102
              Ok (Some full_path))
29✔
103
            else Ok None)
16✔
104
    | None -> Error NoPackage
59✔
105

106
  let populate_flat_namespace ~root =
107
    let flat_namespace = Hashtbl.create 42 in
×
108
    let () =
×
109
      match
110
        Fs.Directory.fold_files_rec_result
111
          (fun () path ->
112
            let name = Fpath.filename path in
×
113
            Ok (Hashtbl.add flat_namespace name path))
×
114
          () root
115
      with
116
      | Ok () -> ()
×
117
      | Error _ -> assert false
118
      (* The function passed to [fold_files_rec_result] never returns [Error _] *)
119
    in
120
    flat_namespace
121

122
  let find_by_name ?root { table = cache; current_root; _ } ~name =
123
    let package =
×
124
      match (root, current_root) with
125
      | Some pkg, _ | None, Some (pkg, _) -> Ok pkg
×
126
      | None, None -> Error NoRoot
×
127
    in
128
    package >>= fun package ->
129
    match hashtbl_find_opt cache package with
×
130
    | Some { flat = Visited flat; _ } -> Ok (Hashtbl.find_all flat name)
×
131
    | Some ({ flat = Unvisited root; _ } as p) ->
×
132
        let flat = populate_flat_namespace ~root in
133
        Hashtbl.replace cache package { p with flat = Visited flat };
134
        Ok (Hashtbl.find_all flat name)
×
135
    | None -> Error NoPackage
×
136
end
137

138
let () = (ignore Named_roots.find_by_name [@warning "-5"])
139

140
module Accessible_paths : sig
141
  type t
142

143
  val create : directories:Fs.Directory.t list -> t
144

145
  val find : t -> string -> Fs.File.t list
146
end = struct
147
  type t = (string, Fpath.t (* list *)) Hashtbl.t
148

149
  let create ~directories =
150
    let unit_cache = Hashtbl.create 42 in
1,518✔
151
    List.iter
1,518✔
152
      (fun directory ->
153
        try
1,031✔
154
          let files = Sys.readdir (Fs.Directory.to_string directory) in
1,031✔
155
          Array.iter
1,026✔
156
            (fun file ->
157
              let file = Fpath.v file in
17,144✔
158
              if Fpath.has_ext "odoc" file then
17,144✔
159
                Hashtbl.add unit_cache
4,618✔
160
                  (Astring.String.Ascii.capitalize
4,618✔
161
                     (file |> Fpath.rem_ext |> Fpath.basename))
4,618✔
162
                  (Fs.File.append directory file))
4,618✔
163
            files
164
        with Sys_error _ ->
5✔
165
          (* TODO: Raise a warning if a directory given as -I cannot be opened *)
166
          ())
167
      directories;
168
    unit_cache
1,518✔
169

170
  let find t name =
171
    let name = Astring.String.Ascii.capitalize name in
4,148✔
172
    Hashtbl.find_all t name
4,148✔
173
end
174

175
module Hierarchy : sig
176
  (** Represent a file hierarchy and allow file path manipulations that do not
177
      escape it. *)
178

179
  type t
180

181
  type error = [ `Escape_hierarchy ]
182

183
  val make : hierarchy_root:Fs.Directory.t -> current_dir:Fs.Directory.t -> t
184

185
  val resolve_relative : t -> Fs.File.t -> (Fs.File.t, error) result
186
  (** [resolve_relative h relpath] resolve [relpath] relatively to the current
187
      directory, making sure not to escape the hierarchy. *)
188
end = struct
189
  type t = { hierarchy_root : Fs.Directory.t; current_dir : Fs.Directory.t }
190

191
  type error = [ `Escape_hierarchy ]
192

193
  let make ~hierarchy_root ~current_dir = { hierarchy_root; current_dir }
45✔
194

195
  let resolve_relative t relpath =
196
    let path = Fs.File.append t.current_dir relpath in
37✔
197
    if Fs.Directory.contains ~parentdir:t.hierarchy_root path then Ok path
37✔
198
    else Error `Escape_hierarchy
×
199
end
200

201
module StringMap = Map.Make (String)
202

203
let build_imports_map imports =
204
  List.fold_left
469✔
205
    (fun map import ->
206
      match import with
1,237✔
207
      | Odoc_model.Lang.Compilation_unit.Import.Unresolved (name, _) ->
1,017✔
208
          StringMap.add name import map
209
      | Odoc_model.Lang.Compilation_unit.Import.Resolved (_, name) ->
220✔
210
          StringMap.add (Odoc_model.Names.ModuleName.to_string name) import map)
220✔
211
    StringMap.empty imports
212

213
let root_name root = Odoc_model.Root.Odoc_file.name root.Odoc_model.Root.file
485✔
214

215
let unit_name
216
    ( Odoc_file.Unit_content { root; _ }
217
    | Page_content { root; _ }
218
    | Impl_content { root; _ }
219
    | Asset_content { root; _ } ) =
220
  root_name root
485✔
221

222
let unit_cache = Hashtbl.create 42
1,118✔
223

224
let load_unit_from_file path =
225
  try Hashtbl.find unit_cache path
660✔
226
  with Not_found ->
377✔
227
    let r = Odoc_file.load path >>= fun u -> Ok u.content in
354✔
228
    Hashtbl.add unit_cache path r;
377✔
229
    r
377✔
230

231
let self = ref None
232

233
(** Load every units matching a given name. Cached. *)
234
let load_units_from_name =
235
  let safe_read file acc =
236
    match load_unit_from_file file with
955✔
237
    | Ok u -> u :: acc
955✔
238
    | Error (`Msg msg) ->
×
239
        (* TODO: Propagate warnings instead of printing. *)
240
        let warning =
241
          Odoc_model.Error.filename_only "%s" msg (Fs.File.to_string file)
×
242
        in
243
        prerr_endline (Odoc_model.Error.to_string warning);
×
244
        acc
×
245
  in
246
  let do_load ap target_name =
247
    let paths = Accessible_paths.find ap target_name in
3,394✔
248
    List.fold_right safe_read paths []
3,394✔
249
  in
250
  let check_self name =
251
    match !self with
3,463✔
252
    | Some (n, unit) -> if n = name then Some unit else None
69✔
253
    | None -> None
215✔
254
  in
255
  fun ap target_name ->
256
    match check_self target_name with
3,463✔
257
    | Some unit -> [ unit ]
69✔
258
    | None -> do_load ap target_name
3,394✔
259

260
let rec find_map f = function
261
  | [] -> None
2,575✔
262
  | hd :: tl -> (
1,024✔
263
      match f hd with Some x -> Some (x, tl) | None -> find_map f tl)
×
264

265
let lookup_unit_with_digest ap target_name digest =
266
  let unit_that_match_digest u =
878✔
267
    match u with
389✔
268
    | Odoc_file.Unit_content m
389✔
269
      when Digest.compare m.Odoc_model.Lang.Compilation_unit.digest digest = 0
389✔
270
      ->
271
        Some m
389✔
272
    | _ -> None
×
273
  in
274
  let units = load_units_from_name ap target_name in
275
  match find_map unit_that_match_digest units with
878✔
276
  | Some (m, _) -> Ok (Odoc_xref2.Env.Found m)
389✔
277
  | None -> Error `Not_found
489✔
278

279
(** Lookup a compilation unit matching a name. If there is more than one
280
    result, report on stderr and return the first one.
281

282
    TODO: Correctly propagate warnings instead of printing. *)
283
let lookup_unit_by_name ap target_name =
284
  let first_unit u =
258✔
285
    match u with
136✔
286
    | Odoc_file.Unit_content m -> Some m
136✔
287
    | Impl_content _ | Page_content _ | Asset_content _ -> None
×
288
  in
289
  let rec find_ambiguous tl =
290
    match find_map first_unit tl with
136✔
291
    | Some (m, tl) -> m :: find_ambiguous tl
×
292
    | None -> []
136✔
293
  in
294
  let units = load_units_from_name ap target_name in
295
  match find_map first_unit units with
258✔
296
  | Some (m, tl) ->
136✔
297
      (match find_ambiguous tl with
298
      | [] -> ()
136✔
299
      | ambiguous ->
×
300
          let ambiguous = m :: ambiguous in
301
          let ambiguous =
302
            List.map
303
              (fun m -> root_name m.Odoc_model.Lang.Compilation_unit.root)
×
304
              ambiguous
305
          in
306
          let warning =
×
307
            Odoc_model.Error.filename_only
308
              "Ambiguous lookup. Possible files: %a"
309
              Format.(pp_print_list pp_print_string)
×
310
              ambiguous target_name
311
          in
312
          prerr_endline (Odoc_model.Error.to_string warning));
×
313
      Some m
314
  | None -> None
122✔
315

316
(** Lookup an unit. First looks into [imports_map] then searches into the
317
    paths. *)
318
let lookup_unit_by_name ~important_digests ~imports_map ap target_name =
319
  let of_option f =
1,150✔
320
    match f with
258✔
321
    | Some m -> Ok (Odoc_xref2.Env.Found m)
136✔
322
    | None -> Error `Not_found
122✔
323
  in
324
  match StringMap.find target_name imports_map with
325
  | Odoc_model.Lang.Compilation_unit.Import.Unresolved (_, Some digest) ->
506✔
326
      lookup_unit_with_digest ap target_name digest
327
  | Unresolved (_, None) ->
16✔
328
      if important_digests then Ok Odoc_xref2.Env.Forward_reference
11✔
329
      else of_option (lookup_unit_by_name ap target_name)
5✔
330
  | Resolved (root, _) -> lookup_unit_with_digest ap target_name root.digest
372✔
331
  | exception Not_found ->
256✔
332
      if important_digests then Error `Not_found
3✔
333
      else of_option (lookup_unit_by_name ap target_name)
253✔
334

335
(** Lookup a page.
336

337
    TODO: Warning on ambiguous lookup. *)
338
let lookup_page_by_name ap target_name =
339
  let target_name = "page-" ^ target_name in
66✔
340
  let is_page u =
341
    match u with
47✔
342
    | Odoc_file.Page_content p -> Some p
47✔
343
    | Impl_content _ | Unit_content _ | Asset_content _ -> None
×
344
  in
345
  let units = load_units_from_name ap target_name in
346
  match find_map is_page units with
66✔
347
  | Some (p, _) -> Ok p
47✔
348
  | None -> Error `Not_found
19✔
349

350
(** Lookup an implementation. *)
351
let lookup_impl ap target_name =
352
  let target_name = "impl-" ^ Astring.String.Ascii.uncapitalize target_name in
2,261✔
353
  let is_impl u =
354
    match u with
452✔
355
    | Odoc_file.Impl_content p -> Some p
452✔
356
    | Page_content _ | Unit_content _ | Asset_content _ -> None
×
357
  in
358
  let units = load_units_from_name ap target_name in
359
  match find_map is_impl units with Some (p, _) -> Some p | None -> None
452✔
360

361
(** Add the current unit to the cache. No need to load other units with the same
362
    name. *)
363
let add_unit_to_cache u =
364
  let target_name =
485✔
365
    (match u with
366
    | Odoc_file.Page_content _ -> "page-"
78✔
367
    | Impl_content _ -> "impl-"
×
368
    | Unit_content _ -> ""
407✔
369
    | Asset_content _ -> "asset-")
×
370
    ^ unit_name u
485✔
371
  in
372
  self := Some (target_name, u)
373

374
(** Resolve a path reference in the given named roots and hierarchy.
375
    [possible_unit_names] should return a list of possible file names for the
376
    given unit name. *)
377
let lookup_path ~possible_unit_names ~named_roots ~hierarchy (tag, path) :
378
    (Odoc_file.content, [ `Not_found ]) result =
379
  let open Odoc_utils.OptionMonad in
123✔
380
  let option_to_result = function Some p -> Ok p | None -> Error `Not_found in
57✔
381
  (* TODO: We might want to differentiate when the file is not found and when
382
     an unexpected error occurred. *)
383
  let handle_load_error = function Ok u -> Some u | Error (`Msg _) -> None in
25✔
384
  let ref_path_to_file_path path =
385
    match List.rev path with
123✔
386
    | [] -> []
×
387
    | name :: rest ->
123✔
388
        List.map
389
          (fun fname -> List.rev (fname :: rest) |> Fs.File.of_segs)
179✔
390
          (possible_unit_names name)
123✔
391
  in
392
  let find_by_path ?root named_roots path =
393
    match Named_roots.find_by_path ?root named_roots ~path with
142✔
394
    | Ok x -> x
61✔
395
    | Error (NoPackage | NoRoot) -> None
22✔
396
  in
397
  let find_in_named_roots ?root path =
398
    named_roots >>= fun named_roots ->
142✔
399
    find_by_path ?root named_roots path >>= fun path ->
142✔
400
    load_unit_from_file path |> handle_load_error
45✔
401
  in
402
  let find_in_hierarchy path =
403
    hierarchy >>= fun hierarchy ->
37✔
404
    match Hierarchy.resolve_relative hierarchy path with
37✔
405
    | Ok path -> load_unit_from_file path |> handle_load_error
37✔
406
    | Error `Escape_hierarchy -> None (* TODO: propagate more information *)
×
407
  in
408
  match tag with
409
  | `TCurrentPackage ->
34✔
410
      (* [path] is within the current package root. *)
411
      ref_path_to_file_path path
412
      |> List.find_map find_in_named_roots
34✔
413
      |> option_to_result
34✔
414
  | `TAbsolutePath ->
62✔
415
      (match path with
416
      | root :: path ->
62✔
417
          ref_path_to_file_path path
418
          |> List.find_map (find_in_named_roots ~root)
62✔
419
      | [] -> None)
×
420
      |> option_to_result
421
  | `TRelativePath ->
27✔
422
      ref_path_to_file_path path
423
      |> List.find_map find_in_hierarchy
27✔
424
      |> option_to_result
27✔
425

426
let lookup_asset_by_path ~pages ~hierarchy path =
427
  let possible_unit_names name = [ "asset-" ^ name ^ ".odoc" ] in
9✔
428
  match lookup_path ~possible_unit_names ~named_roots:pages ~hierarchy path with
429
  | Ok (Odoc_file.Asset_content asset) -> Ok asset
6✔
430
  | Ok _ -> Error `Not_found (* TODO: Report is not an asset. *)
×
431
  | Error _ as e -> e
3✔
432

433
let lookup_page_by_path ~pages ~hierarchy path =
434
  let possible_unit_names name = [ "page-" ^ name ^ ".odoc" ] in
58✔
435
  match lookup_path ~possible_unit_names ~named_roots:pages ~hierarchy path with
436
  | Ok (Odoc_file.Page_content page) -> Ok page
47✔
437
  | Ok _ -> Error `Not_found (* TODO: Report is not a page. *)
×
438
  | Error _ as e -> e
11✔
439

440
let lookup_unit_by_path ~libs ~hierarchy path =
441
  let possible_unit_names name =
56✔
442
    Astring.String.Ascii.
56✔
443
      [ capitalize name ^ ".odoc"; uncapitalize name ^ ".odoc" ]
56✔
444
  in
445
  match lookup_path ~possible_unit_names ~named_roots:libs ~hierarchy path with
446
  | Ok (Odoc_file.Unit_content u) -> Ok (Odoc_xref2.Env.Found u)
4✔
447
  | Ok _ -> Error `Not_found (* TODO: Report is not a module. *)
×
448
  | Error _ as e -> e
52✔
449

450
let lookup_unit ~important_digests ~imports_map ap ~libs ~hierarchy = function
451
  | `Path p -> lookup_unit_by_path ~libs ~hierarchy p
56✔
452
  | `Name n -> lookup_unit_by_name ~important_digests ~imports_map ap n
1,150✔
453

454
let lookup_page ap ~pages ~hierarchy = function
455
  | `Path p -> lookup_page_by_path ~pages ~hierarchy p
58✔
456
  | `Name n -> lookup_page_by_name ap n
43✔
457

458
let lookup_asset ~pages ~hierarchy = function
459
  | `Path p -> lookup_asset_by_path ~pages ~hierarchy p
9✔
460
  | `Name _ -> failwith "TODO"
×
461

462
type t = {
463
  important_digests : bool;
464
  ap : Accessible_paths.t;
465
  extended_ap : Accessible_paths.t;
466
  pages : Named_roots.t option;
467
  libs : Named_roots.t option;
468
  open_modules : string list;
469
  current_dir : Fs.Directory.t option;
470
}
471

472
type roots = {
473
  page_roots : named_root list;
474
  lib_roots : named_root list;
475
  current_lib : named_root option;
476
  current_package : named_root option;
477
  current_dir : Fs.Directory.t;
478
}
479

480
let create ~important_digests ~directories ~open_modules ~roots =
481
  let pages, libs, current_dir, directories =
759✔
482
    match roots with
483
    | None -> (None, None, None, directories)
481✔
484
    | Some { page_roots; lib_roots; current_lib; current_package; current_dir }
278✔
485
      ->
486
        let prepare roots =
487
          List.map (fun (name, dir) -> { Named_roots.name; dir }) roots
77✔
488
        in
489
        let directories =
490
          match current_package with
491
          | None -> directories
226✔
492
          | Some (_pkg, dir) -> dir :: directories
52✔
493
        in
494
        let lib_roots = prepare lib_roots in
495
        let page_roots = prepare page_roots in
278✔
496
        let pages = Named_roots.create ~current_root:current_package page_roots
278✔
497
        and libs = Named_roots.create ~current_root:current_lib lib_roots in
278✔
498
        let directories =
499
          List.sort_uniq Fs.Directory.compare (current_dir :: directories)
500
        in
501
        (Some pages, Some libs, Some current_dir, directories)
278✔
502
  in
503
  let ap = Accessible_paths.create ~directories in
504
  let extended_directories =
505
    match roots with
506
    | None -> directories
481✔
507
    | Some { lib_roots; _ } -> directories @ List.map snd lib_roots
278✔
508
  in
509
  let extended_directories =
510
    List.sort_uniq Fs.Directory.compare extended_directories
511
  in
512
  let extended_ap = Accessible_paths.create ~directories:extended_directories in
759✔
513
  { important_digests; ap; extended_ap; open_modules; pages; libs; current_dir }
514

515
(** Helpers for creating xref2 env. *)
516

517
open Odoc_xref2
518

519
let build_compile_env_for_unit
520
    {
521
      important_digests;
522
      ap;
523
      extended_ap = _;
524
      open_modules = open_units;
525
      pages = _;
526
      libs = _;
527
      current_dir = _;
528
    } m =
529
  add_unit_to_cache (Odoc_file.Unit_content m);
235✔
530
  let imports_map = build_imports_map m.imports in
235✔
531
  (* Do not implement [lookup_page] in compile mode, as that might return
532
     different results depending on the compilation order.
533
     On the other hand, [lookup_unit] is needed at compile time and the
534
     compilation order is known by the driver. *)
535
  let lookup_unit =
235✔
536
    lookup_unit ~important_digests ~imports_map ap ~libs:None ~hierarchy:None
235✔
537
  and lookup_page _ = Error `Not_found
×
538
  and lookup_asset _ = Error `Not_found
×
539
  and lookup_impl = lookup_impl ap in
235✔
540
  let resolver =
541
    { Env.open_units; lookup_unit; lookup_page; lookup_impl; lookup_asset }
542
  in
543
  Env.env_of_unit m ~linking:false resolver
544

545
(** [important_digests] and [imports_map] only apply to modules. *)
546
let build ?(imports_map = StringMap.empty) ?hierarchy_roots
83✔
547
    {
548
      important_digests;
549
      ap;
550
      extended_ap;
551
      open_modules = open_units;
552
      pages;
553
      libs;
554
      current_dir;
555
    } =
556
  let hierarchy =
317✔
557
    let open OptionMonad in
558
    current_dir >>= fun current_dir ->
317✔
559
    hierarchy_roots >>= Named_roots.current_root >>= fun hierarchy_root ->
278✔
560
    Some (Hierarchy.make ~hierarchy_root ~current_dir)
45✔
561
  in
562
  let lookup_unit =
563
    lookup_unit ~important_digests ~imports_map extended_ap ~libs ~hierarchy
317✔
564
  and lookup_page = lookup_page ap ~pages ~hierarchy
317✔
565
  and lookup_asset = lookup_asset ~pages ~hierarchy
566
  and lookup_impl = lookup_impl ap in
317✔
567
  { Env.open_units; lookup_unit; lookup_page; lookup_impl; lookup_asset }
568

569
let build_compile_env_for_impl t i =
570
  let imports_map =
32✔
571
    build_imports_map i.Odoc_model.Lang.Implementation.imports
572
  in
573
  let resolver = build ~imports_map t in
32✔
574
  Env.env_of_impl i resolver
32✔
575

576
let build_link_env_for_unit t m =
577
  add_unit_to_cache (Odoc_file.Unit_content m);
172✔
578
  let imports_map = build_imports_map m.imports in
172✔
579
  let resolver = build ~imports_map ?hierarchy_roots:t.libs t in
172✔
580
  Env.env_of_unit m ~linking:true resolver
172✔
581

582
let build_link_env_for_impl t i =
583
  let imports_map =
30✔
584
    build_imports_map i.Odoc_model.Lang.Implementation.imports
585
  in
586
  let resolver = build ~imports_map t in
30✔
587
  Env.env_of_impl i resolver
30✔
588

589
let build_env_for_page t p =
590
  add_unit_to_cache (Odoc_file.Page_content p);
78✔
591
  let resolver =
78✔
592
    build ?hierarchy_roots:t.pages { t with important_digests = false }
593
  in
594
  Env.env_of_page p resolver
78✔
595

596
let build_env_for_reference t =
597
  let resolver = build { t with important_digests = false } in
5✔
598
  Env.env_for_reference resolver
5✔
599

600
let lookup_page t target_name =
601
  match lookup_page_by_name t.ap target_name with
23✔
602
  | Ok p -> Some p
23✔
603
  | Error `Not_found -> None
×
604

605
let resolve_import t target_name =
606
  let rec loop = function
754✔
607
    | [] -> None
581✔
608
    | path :: tl -> (
173✔
609
        match Odoc_file.load_root path with
610
        | Error _ -> loop tl
×
611
        | Ok root -> (
173✔
612
            match root.Odoc_model.Root.file with
613
            | Compilation_unit _ -> Some root
173✔
614
            | Impl _ | Page _ | Asset _ -> loop tl))
×
615
  in
616
  loop (Accessible_paths.find t.ap target_name)
754✔
STATUS · Troubleshooting · Open an Issue · Sales · Support · CAREERS · ENTERPRISE · START FREE · SCHEDULE DEMO
ANNOUNCEMENTS · TWITTER · TOS & SLA · Supported CI Services · What's a CI service? · Automated Testing

© 2026 Coveralls, Inc