Skip to content

Commit

Permalink
Rename Lang field locs → source_loc
Browse files Browse the repository at this point in the history
This field now hold one location instead of two. The name is now more
explicit.
  • Loading branch information
Julow committed Jan 18, 2024
1 parent 00571b4 commit 830c4ed
Show file tree
Hide file tree
Showing 22 changed files with 272 additions and 259 deletions.
22 changes: 11 additions & 11 deletions src/document/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -53,10 +53,10 @@ let path_to_id path =
| Error _ -> None
| Ok url -> Some url

let source_anchor locs =
let source_anchor source_loc =
(* Remove when dropping support for OCaml < 4.08 *)
let to_option = function Result.Ok x -> Some x | Result.Error _ -> None in
match locs with
match source_loc with
| Some id ->
Url.Anchor.from_identifier
(id : Paths.Identifier.SourceLocation.t :> Paths.Identifier.t)
Expand Down Expand Up @@ -690,7 +690,7 @@ module Make (Syntax : SYNTAX) = struct
(* Take the anchor from the first constructor only for consistency with
regular variants. *)
match t.constructors with
| hd :: _ -> source_anchor hd.locs
| hd :: _ -> source_anchor hd.source_loc
| [] -> None
in
Item.Declaration { attr; anchor; doc; content; source_anchor }
Expand All @@ -706,7 +706,7 @@ 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
let source_anchor = source_anchor t.locs in
let source_anchor = source_anchor t.source_loc in
Item.Declaration { attr; anchor; doc; content; source_anchor }

let polymorphic_variant ~type_ident
Expand Down Expand Up @@ -919,7 +919,7 @@ 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
let source_anchor = source_anchor t.locs in
let source_anchor = source_anchor t.source_loc in
Item.Declaration { attr; anchor; doc; content; source_anchor }
end

Expand Down Expand Up @@ -947,7 +947,7 @@ 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
let source_anchor = source_anchor t.locs in
let source_anchor = source_anchor t.source_loc in
Item.Declaration { attr; anchor; doc; content; source_anchor }
end

Expand Down Expand Up @@ -1144,7 +1144,7 @@ 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 source_anchor = source_anchor t.source_loc in
let cname, expansion, expansion_doc =
match t.expansion with
| None -> (O.documentedSrc @@ O.txt name, None, None)
Expand Down Expand Up @@ -1182,7 +1182,7 @@ 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 source_anchor = source_anchor t.source_loc in
let cname, expansion, expansion_doc =
match t.expansion with
| None -> (O.documentedSrc @@ O.txt name, None, None)
Expand Down Expand Up @@ -1445,7 +1445,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 source_anchor = source_anchor t.source_loc in
let modname, status, expansion, expansion_doc =
match expansion with
| None -> (O.txt modname, `Default, None, None)
Expand Down Expand Up @@ -1540,7 +1540,7 @@ 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 source_anchor = source_anchor t.source_loc in
let modname, expansion_doc, mty =
module_type_manifest ~subst:false ~source_anchor modname t.id t.doc
t.expr prefix
Expand Down Expand Up @@ -1806,7 +1806,7 @@ module Make (Syntax : SYNTAX) = struct
| Module sign -> signature sign
| Pack packed -> ([], pack packed)
in
let source_anchor = source_anchor t.locs in
let source_anchor = source_anchor t.source_loc in
let page = make_expansion_page ~source_anchor url [ unit_doc ] items in
Document.Page page

Expand Down
32 changes: 16 additions & 16 deletions src/loader/cmi.ml
Original file line number Diff line number Diff line change
Expand Up @@ -578,7 +578,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 source_loc = None in
let container =
(parent : Identifier.Signature.t :> Identifier.LabelParent.t)
in
Expand All @@ -597,7 +597,7 @@ let read_value_description env parent id vd =
External primitives
| _ -> assert false
in
Value { Value.id; locs; doc; type_; value }
Value { Value.id; source_loc; doc; type_; value }

let read_label_declaration env parent ld =
let open TypeDecl.Field in
Expand Down Expand Up @@ -704,7 +704,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 source_loc = 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
Expand Down Expand Up @@ -735,20 +735,20 @@ 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; locs; doc; canonical; equation; representation}
{id; source_loc; doc; canonical; equation; representation}

let read_extension_constructor env parent id ext =
let open Extension.Constructor in
let id = Env.find_extension_identifier env id in
let locs = None in
let source_loc = 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 =
read_constructor_declaration_arguments env
(parent : Identifier.Signature.t :> Identifier.FieldParent.t) ext.ext_args
in
let res = opt_map (read_type_expr env) ext.ext_ret_type in
{id; locs; doc; args; res}
{id; source_loc; doc; args; res}

let read_type_extension env parent id ext rest =
let open Extension in
Expand All @@ -773,7 +773,7 @@ let read_type_extension env parent id ext rest =
let read_exception env parent id ext =
let open Exception in
let id = Env.find_exception_identifier env id in
let locs = None in
let source_loc = 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;
Expand All @@ -782,7 +782,7 @@ let read_exception env parent id ext =
(parent : Identifier.Signature.t :> Identifier.FieldParent.t) ext.ext_args
in
let res = opt_map (read_type_expr env) ext.ext_ret_type in
{id; locs; doc; args; res}
{id; source_loc; doc; args; res}

let read_method env parent concrete (name, kind, typ) =
let open Method in
Expand Down Expand Up @@ -867,7 +867,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 source_loc = 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;
Expand All @@ -880,7 +880,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; locs; doc; virtual_; params; expr; expansion = None }
{ id; source_loc; doc; virtual_; params; expr; expansion = None }

let rec read_class_type env parent params =
let open Class in function
Expand All @@ -903,7 +903,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 source_loc = 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;
Expand All @@ -916,7 +916,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; locs; doc; virtual_; params; type_; expansion = None }
{ id; source_loc; doc; virtual_; params; type_; expansion = None }

let rec read_module_type env parent (mty : Odoc_model.Compat.module_type) =
let open ModuleType in
Expand Down Expand Up @@ -945,17 +945,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 source_loc = 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; locs; doc; canonical; expr }
{id; source_loc; 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 source_loc = 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
Expand All @@ -969,7 +969,7 @@ and read_module_declaration env parent ident (md : Odoc_model.Compat.module_decl
| Some _ -> false
| None -> Odoc_model.Names.contains_double_underscore (Ident.name ident)
in
{id; locs; doc; type_; canonical; hidden }
{id; source_loc; doc; type_; canonical; hidden }

and read_type_rec_status rec_status =
let open Signature in
Expand Down
14 changes: 7 additions & 7 deletions src/loader/cmt.ml
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ 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 source_loc = None in
let open Signature in
match pat.pat_desc with
| Tpat_any -> []
Expand All @@ -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; locs = locs id; doc; type_; value}]
[Value {id; source_loc; 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; locs = locs id; doc; type_; value} :: read_pattern env parent doc pat
Value {id; source_loc; doc; type_; value} :: read_pattern env parent doc pat
| Tpat_constant _ -> []
| Tpat_tuple pats ->
List.concat (List.map (read_pattern env parent doc) pats)
Expand Down Expand Up @@ -324,7 +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 source_loc = 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;
Expand All @@ -338,7 +338,7 @@ let read_class_declaration env parent cld =
clparams
in
let type_ = read_class_expr env (id :> Identifier.ClassSignature.t) clparams cld.ci_expr in
{ id; locs; doc; virtual_; params; type_; expansion = None }
{ id; source_loc; doc; virtual_; params; type_; expansion = None }

let read_class_declarations env parent clds =
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t) in
Expand Down Expand Up @@ -432,7 +432,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 source_loc = 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 =
Expand All @@ -457,7 +457,7 @@ and read_module_binding env parent mb =
| _ -> false
#endif
in
Some {id; locs; doc; type_; canonical; hidden; }
Some {id; source_loc; doc; type_; canonical; hidden; }

and read_module_bindings env parent mbs =
let container = (parent : Identifier.Signature.t :> Identifier.LabelParent.t)
Expand Down
Loading

0 comments on commit 830c4ed

Please sign in to comment.