Skip to content

Commit af9c421

Browse files
committed
Move version-dependent code from odoc_loader to implementation
1 parent 3e78a38 commit af9c421

File tree

3 files changed

+32
-36
lines changed

3 files changed

+32
-36
lines changed

src/loader/implementation.ml

Lines changed: 23 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -503,8 +503,30 @@ let of_cmt (source_id : Odoc_model.Paths.Identifier.SourcePage.t)
503503

504504
(uid_to_id, postprocess_poses source_id vs uid_to_id uid_to_loc)
505505

506+
let read_cmt_infos source_id_opt id cmt_info =
507+
match Odoc_model.Compat.shape_of_cmt_infos cmt_info with
508+
| Some shape -> (
509+
let uid_to_loc = cmt_info.cmt_uid_to_loc in
510+
match (source_id_opt, cmt_info.cmt_annots) with
511+
| Some source_id, Implementation impl ->
512+
let map, source_infos =
513+
of_cmt source_id id impl uid_to_loc
514+
in
515+
( Some shape,
516+
map,
517+
Some
518+
{
519+
Odoc_model.Lang.Source_info.id = source_id;
520+
infos = source_infos;
521+
} )
522+
| _, _ -> (Some shape, Odoc_model.Compat.empty_map, None))
523+
| None -> (None, Odoc_model.Compat.empty_map, None)
524+
525+
526+
506527
#else
507528

508-
let of_cmt _ _ _ _ = (), []
529+
let read_cmt_infos _source_id_opt _id ~filename:_ () =
530+
(None, Odoc_model.Compat.empty_map, None)
509531

510532
#endif

src/loader/implementation.mli

Lines changed: 8 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,11 @@
1-
val of_cmt :
2-
Odoc_model.Paths.Identifier.SourcePage.t ->
3-
Odoc_model.Paths.Identifier.RootModule.t ->
4-
Typedtree.structure ->
5-
Odoc_model.Compat.uid_to_loc ->
6-
Odoc_model.Paths.Identifier.Id.source_location Odoc_model.Compat.shape_uid_map
7-
* Odoc_model.Lang.Source_info.infos
1+
val read_cmt_infos :
2+
Odoc_model.Paths.Identifier.Id.source_page option ->
3+
Odoc_model.Paths.Identifier.Id.root_module ->
4+
Cmt_format.cmt_infos ->
5+
Odoc_model.Compat.shape option
6+
* Odoc_model.Paths.Identifier.Id.source_location
7+
Odoc_model.Compat.shape_uid_map
8+
* Odoc_model.Lang.Source_info.t option
89
(** Extract all implementation information from a [cmt]: the shape, and the
910
{{!Odoc_model.Lang.Source_info.infos}source infos} (local and global
1011
definitions and occurrences).

src/loader/odoc_loader.ml

Lines changed: 1 addition & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -42,41 +42,14 @@ exception Not_an_interface
4242

4343
exception Make_root_error of string
4444

45-
#if OCAML_VERSION >= (4, 14, 0)
46-
(** [cmt_info.cmt_annots = Implementation _] *)
47-
let read_cmt_infos' source_id_opt id cmt_info =
48-
match Odoc_model.Compat.shape_of_cmt_infos cmt_info with
49-
| Some shape -> (
50-
let uid_to_loc = cmt_info.cmt_uid_to_loc in
51-
match (source_id_opt, cmt_info.cmt_annots) with
52-
| Some source_id, Implementation impl ->
53-
let map, source_infos =
54-
Implementation.of_cmt source_id id impl uid_to_loc
55-
in
56-
( Some shape,
57-
map,
58-
Some
59-
{
60-
Odoc_model.Lang.Source_info.id = source_id;
61-
infos = source_infos;
62-
} )
63-
| _, _ -> (Some shape, Odoc_model.Compat.empty_map, None))
64-
| None -> (None, Odoc_model.Compat.empty_map, None)
65-
6645
let read_cmt_infos source_id_opt id ~filename () =
6746
match Cmt_format.read_cmt filename with
6847
| exception Cmi_format.Error _ -> raise Corrupted
6948
| cmt_info -> (
7049
match cmt_info.cmt_annots with
71-
| Implementation _ -> read_cmt_infos' source_id_opt id cmt_info
50+
| Implementation _ -> Implementation.read_cmt_infos source_id_opt id cmt_info
7251
| _ -> raise Not_an_implementation)
7352

74-
#else
75-
76-
let read_cmt_infos _source_id_opt _id ~filename:_ () =
77-
(None, Odoc_model.Compat.empty_map, None)
78-
79-
#endif
8053

8154
let make_compilation_unit ~make_root ~imports ~interface ?sourcefile ~name ~id
8255
?canonical ?shape ~uid_to_id ~source_info content =

0 commit comments

Comments
 (0)