Skip to content

Commit 830c4ed

Browse files
committed
Rename Lang field locs → source_loc
This field now hold one location instead of two. The name is now more explicit.
1 parent 00571b4 commit 830c4ed

File tree

22 files changed

+272
-259
lines changed

22 files changed

+272
-259
lines changed

src/document/generator.ml

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -53,10 +53,10 @@ let path_to_id path =
5353
| Error _ -> None
5454
| Ok url -> Some url
5555

56-
let source_anchor locs =
56+
let source_anchor source_loc =
5757
(* Remove when dropping support for OCaml < 4.08 *)
5858
let to_option = function Result.Ok x -> Some x | Result.Error _ -> None in
59-
match locs with
59+
match source_loc with
6060
| Some id ->
6161
Url.Anchor.from_identifier
6262
(id : Paths.Identifier.SourceLocation.t :> Paths.Identifier.t)
@@ -690,7 +690,7 @@ module Make (Syntax : SYNTAX) = struct
690690
(* Take the anchor from the first constructor only for consistency with
691691
regular variants. *)
692692
match t.constructors with
693-
| hd :: _ -> source_anchor hd.locs
693+
| hd :: _ -> source_anchor hd.source_loc
694694
| [] -> None
695695
in
696696
Item.Declaration { attr; anchor; doc; content; source_anchor }
@@ -706,7 +706,7 @@ module Make (Syntax : SYNTAX) = struct
706706
let attr = [ "exception" ] in
707707
let anchor = path_to_id t.id in
708708
let doc = Comment.to_ir t.doc in
709-
let source_anchor = source_anchor t.locs in
709+
let source_anchor = source_anchor t.source_loc in
710710
Item.Declaration { attr; anchor; doc; content; source_anchor }
711711

712712
let polymorphic_variant ~type_ident
@@ -919,7 +919,7 @@ module Make (Syntax : SYNTAX) = struct
919919
let attr = "type" :: (if is_substitution then [ "subst" ] else []) in
920920
let anchor = path_to_id t.id in
921921
let doc = Comment.to_ir t.doc in
922-
let source_anchor = source_anchor t.locs in
922+
let source_anchor = source_anchor t.source_loc in
923923
Item.Declaration { attr; anchor; doc; content; source_anchor }
924924
end
925925

@@ -947,7 +947,7 @@ module Make (Syntax : SYNTAX) = struct
947947
let attr = [ "value" ] @ extra_attr in
948948
let anchor = path_to_id t.id in
949949
let doc = Comment.to_ir t.doc in
950-
let source_anchor = source_anchor t.locs in
950+
let source_anchor = source_anchor t.source_loc in
951951
Item.Declaration { attr; anchor; doc; content; source_anchor }
952952
end
953953

@@ -1144,7 +1144,7 @@ module Make (Syntax : SYNTAX) = struct
11441144
if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
11451145
in
11461146

1147-
let source_anchor = source_anchor t.locs in
1147+
let source_anchor = source_anchor t.source_loc in
11481148
let cname, expansion, expansion_doc =
11491149
match t.expansion with
11501150
| None -> (O.documentedSrc @@ O.txt name, None, None)
@@ -1182,7 +1182,7 @@ module Make (Syntax : SYNTAX) = struct
11821182
let virtual_ =
11831183
if t.virtual_ then O.keyword "virtual" ++ O.txt " " else O.noop
11841184
in
1185-
let source_anchor = source_anchor t.locs in
1185+
let source_anchor = source_anchor t.source_loc in
11861186
let cname, expansion, expansion_doc =
11871187
match t.expansion with
11881188
| None -> (O.documentedSrc @@ O.txt name, None, None)
@@ -1445,7 +1445,7 @@ module Make (Syntax : SYNTAX) = struct
14451445
| Alias (_, None) -> None
14461446
| ModuleType e -> expansion_of_module_type_expr e
14471447
in
1448-
let source_anchor = source_anchor t.locs in
1448+
let source_anchor = source_anchor t.source_loc in
14491449
let modname, status, expansion, expansion_doc =
14501450
match expansion with
14511451
| None -> (O.txt modname, `Default, None, None)
@@ -1540,7 +1540,7 @@ module Make (Syntax : SYNTAX) = struct
15401540
O.keyword "module" ++ O.txt " " ++ O.keyword "type" ++ O.txt " "
15411541
in
15421542
let modname = Paths.Identifier.name t.id in
1543-
let source_anchor = source_anchor t.locs in
1543+
let source_anchor = source_anchor t.source_loc in
15441544
let modname, expansion_doc, mty =
15451545
module_type_manifest ~subst:false ~source_anchor modname t.id t.doc
15461546
t.expr prefix
@@ -1806,7 +1806,7 @@ module Make (Syntax : SYNTAX) = struct
18061806
| Module sign -> signature sign
18071807
| Pack packed -> ([], pack packed)
18081808
in
1809-
let source_anchor = source_anchor t.locs in
1809+
let source_anchor = source_anchor t.source_loc in
18101810
let page = make_expansion_page ~source_anchor url [ unit_doc ] items in
18111811
Document.Page page
18121812

src/loader/cmi.ml

Lines changed: 16 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -578,7 +578,7 @@ and read_object env fi nm =
578578
let read_value_description env parent id vd =
579579
let open Signature in
580580
let id = Env.find_value_identifier env id in
581-
let locs = None in
581+
let source_loc = None in
582582
let container =
583583
(parent : Identifier.Signature.t :> Identifier.LabelParent.t)
584584
in
@@ -597,7 +597,7 @@ let read_value_description env parent id vd =
597597
External primitives
598598
| _ -> assert false
599599
in
600-
Value { Value.id; locs; doc; type_; value }
600+
Value { Value.id; source_loc; doc; type_; value }
601601

602602
let read_label_declaration env parent ld =
603603
let open TypeDecl.Field in
@@ -704,7 +704,7 @@ let read_class_constraints env params =
704704
let read_type_declaration env parent id decl =
705705
let open TypeDecl in
706706
let id = Env.find_type_identifier env id in
707-
let locs = None in
707+
let source_loc = None in
708708
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
709709
let doc, canonical =
710710
Doc_attr.attached Odoc_model.Semantics.Expect_canonical container decl.type_attributes
@@ -735,20 +735,20 @@ let read_type_declaration env parent id decl =
735735
in
736736
let private_ = (decl.type_private = Private) in
737737
let equation = Equation.{params; manifest; constraints; private_} in
738-
{id; locs; doc; canonical; equation; representation}
738+
{id; source_loc; doc; canonical; equation; representation}
739739

740740
let read_extension_constructor env parent id ext =
741741
let open Extension.Constructor in
742742
let id = Env.find_extension_identifier env id in
743-
let locs = None in
743+
let source_loc = None in
744744
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
745745
let doc = Doc_attr.attached_no_tag container ext.ext_attributes in
746746
let args =
747747
read_constructor_declaration_arguments env
748748
(parent : Identifier.Signature.t :> Identifier.FieldParent.t) ext.ext_args
749749
in
750750
let res = opt_map (read_type_expr env) ext.ext_ret_type in
751-
{id; locs; doc; args; res}
751+
{id; source_loc; doc; args; res}
752752

753753
let read_type_extension env parent id ext rest =
754754
let open Extension in
@@ -773,7 +773,7 @@ let read_type_extension env parent id ext rest =
773773
let read_exception env parent id ext =
774774
let open Exception in
775775
let id = Env.find_exception_identifier env id in
776-
let locs = None in
776+
let source_loc = None in
777777
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
778778
let doc = Doc_attr.attached_no_tag container ext.ext_attributes in
779779
mark_exception ext;
@@ -782,7 +782,7 @@ let read_exception env parent id ext =
782782
(parent : Identifier.Signature.t :> Identifier.FieldParent.t) ext.ext_args
783783
in
784784
let res = opt_map (read_type_expr env) ext.ext_ret_type in
785-
{id; locs; doc; args; res}
785+
{id; source_loc; doc; args; res}
786786

787787
let read_method env parent concrete (name, kind, typ) =
788788
let open Method in
@@ -867,7 +867,7 @@ let rec read_virtual = function
867867
let read_class_type_declaration env parent id cltd =
868868
let open ClassType in
869869
let id = Env.find_class_type_identifier env id in
870-
let locs = None in
870+
let source_loc = None in
871871
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
872872
let doc = Doc_attr.attached_no_tag container cltd.clty_attributes in
873873
mark_class_type_declaration cltd;
@@ -880,7 +880,7 @@ let read_class_type_declaration env parent id cltd =
880880
read_class_signature env (id :> Identifier.ClassSignature.t) cltd.clty_params cltd.clty_type
881881
in
882882
let virtual_ = read_virtual cltd.clty_type in
883-
{ id; locs; doc; virtual_; params; expr; expansion = None }
883+
{ id; source_loc; doc; virtual_; params; expr; expansion = None }
884884

885885
let rec read_class_type env parent params =
886886
let open Class in function
@@ -903,7 +903,7 @@ let rec read_class_type env parent params =
903903
let read_class_declaration env parent id cld =
904904
let open Class in
905905
let id = Env.find_class_identifier env id in
906-
let locs = None in
906+
let source_loc = None in
907907
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
908908
let doc = Doc_attr.attached_no_tag container cld.cty_attributes in
909909
mark_class_declaration cld;
@@ -916,7 +916,7 @@ let read_class_declaration env parent id cld =
916916
read_class_type env (id :> Identifier.ClassSignature.t) cld.cty_params cld.cty_type
917917
in
918918
let virtual_ = cld.cty_new = None in
919-
{ id; locs; doc; virtual_; params; type_; expansion = None }
919+
{ id; source_loc; doc; virtual_; params; type_; expansion = None }
920920

921921
let rec read_module_type env parent (mty : Odoc_model.Compat.module_type) =
922922
let open ModuleType in
@@ -945,17 +945,17 @@ let rec read_module_type env parent (mty : Odoc_model.Compat.module_type) =
945945
and read_module_type_declaration env parent id (mtd : Odoc_model.Compat.modtype_declaration) =
946946
let open ModuleType in
947947
let id = Env.find_module_type env id in
948-
let locs = None in
948+
let source_loc = None in
949949
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
950950
let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container mtd.mtd_attributes in
951951
let canonical = (canonical :> Path.ModuleType.t option) in
952952
let expr = opt_map (read_module_type env (id :> Identifier.Signature.t)) mtd.mtd_type in
953-
{id; locs; doc; canonical; expr }
953+
{id; source_loc; doc; canonical; expr }
954954

955955
and read_module_declaration env parent ident (md : Odoc_model.Compat.module_declaration) =
956956
let open Module in
957957
let id = (Env.find_module_identifier env ident :> Identifier.Module.t) in
958-
let locs = None in
958+
let source_loc = None in
959959
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
960960
let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container md.md_attributes in
961961
let canonical = (canonical :> Path.Module.t option) in
@@ -969,7 +969,7 @@ and read_module_declaration env parent ident (md : Odoc_model.Compat.module_decl
969969
| Some _ -> false
970970
| None -> Odoc_model.Names.contains_double_underscore (Ident.name ident)
971971
in
972-
{id; locs; doc; type_; canonical; hidden }
972+
{id; source_loc; doc; type_; canonical; hidden }
973973

974974
and read_type_rec_status rec_status =
975975
let open Signature in

src/loader/cmt.ml

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ let read_core_type env ctyp =
2929
Cmi.read_type_expr env ctyp.ctyp_type
3030

3131
let rec read_pattern env parent doc pat =
32-
let locs _id = None in
32+
let source_loc = None in
3333
let open Signature in
3434
match pat.pat_desc with
3535
| Tpat_any -> []
@@ -39,14 +39,14 @@ let rec read_pattern env parent doc pat =
3939
Cmi.mark_type_expr pat.pat_type;
4040
let type_ = Cmi.read_type_expr env pat.pat_type in
4141
let value = Abstract in
42-
[Value {id; locs = locs id; doc; type_; value}]
42+
[Value {id; source_loc; doc; type_; value}]
4343
| Tpat_alias(pat, id, _) ->
4444
let open Value in
4545
let id = Env.find_value_identifier env id in
4646
Cmi.mark_type_expr pat.pat_type;
4747
let type_ = Cmi.read_type_expr env pat.pat_type in
4848
let value = Abstract in
49-
Value {id; locs = locs id; doc; type_; value} :: read_pattern env parent doc pat
49+
Value {id; source_loc; doc; type_; value} :: read_pattern env parent doc pat
5050
| Tpat_constant _ -> []
5151
| Tpat_tuple pats ->
5252
List.concat (List.map (read_pattern env parent doc) pats)
@@ -324,7 +324,7 @@ let rec read_class_expr env parent params cl =
324324
let read_class_declaration env parent cld =
325325
let open Class in
326326
let id = Env.find_class_identifier env cld.ci_id_class in
327-
let locs = None in
327+
let source_loc = None in
328328
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
329329
let doc = Doc_attr.attached_no_tag container cld.ci_attributes in
330330
Cmi.mark_class_declaration cld.ci_decl;
@@ -338,7 +338,7 @@ let read_class_declaration env parent cld =
338338
clparams
339339
in
340340
let type_ = read_class_expr env (id :> Identifier.ClassSignature.t) clparams cld.ci_expr in
341-
{ id; locs; doc; virtual_; params; type_; expansion = None }
341+
{ id; source_loc; doc; virtual_; params; type_; expansion = None }
342342

343343
let read_class_declarations env parent clds =
344344
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
@@ -432,7 +432,7 @@ and read_module_binding env parent mb =
432432
let id = Env.find_module_identifier env mb.mb_id in
433433
#endif
434434
let id = (id :> Identifier.Module.t) in
435-
let locs = None in
435+
let source_loc = None in
436436
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
437437
let doc, canonical = Doc_attr.attached Odoc_model.Semantics.Expect_canonical container mb.mb_attributes in
438438
let type_, canonical =
@@ -457,7 +457,7 @@ and read_module_binding env parent mb =
457457
| _ -> false
458458
#endif
459459
in
460-
Some {id; locs; doc; type_; canonical; hidden; }
460+
Some {id; source_loc; doc; type_; canonical; hidden; }
461461

462462
and read_module_bindings env parent mbs =
463463
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t)

0 commit comments

Comments
 (0)