Skip to content

Commit 725d900

Browse files
committed
renaming fragment_type_parent to field_parent in resolved ref and id
since they are not used in resolved ref and id of cosntructor: for those, the parent is a type. Signed-off-by: Paul-Elliot <[email protected]>
1 parent bed9ef2 commit 725d900

File tree

11 files changed

+62
-76
lines changed

11 files changed

+62
-76
lines changed

src/loader/cmi.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -632,7 +632,7 @@ let read_constructor_declaration env parent cd =
632632
let doc = Doc_attr.attached_no_tag container cd.cd_attributes in
633633
let args =
634634
read_constructor_declaration_arguments env
635-
(parent :> Identifier.FragmentTypeParent.t) cd.cd_args
635+
(parent :> Identifier.FieldParent.t) cd.cd_args
636636
in
637637
let res = opt_map (read_type_expr env) cd.cd_res in
638638
{id; doc; args; res}
@@ -652,7 +652,7 @@ let read_type_kind env parent =
652652
| Type_record(lbls, _) ->
653653
let lbls =
654654
List.map
655-
(read_label_declaration env (parent :> Identifier.FragmentTypeParent.t))
655+
(read_label_declaration env (parent :> Identifier.FieldParent.t))
656656
lbls
657657
in
658658
Some (Record lbls)
@@ -745,7 +745,7 @@ let read_extension_constructor env parent id ext =
745745
let doc = Doc_attr.attached_no_tag container ext.ext_attributes in
746746
let args =
747747
read_constructor_declaration_arguments env
748-
(parent : Identifier.Signature.t :> Identifier.FragmentTypeParent.t) ext.ext_args
748+
(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
751751
{id; locs; doc; args; res}
@@ -779,7 +779,7 @@ let read_exception env parent id ext =
779779
mark_exception ext;
780780
let args =
781781
read_constructor_declaration_arguments env
782-
(parent : Identifier.Signature.t :> Identifier.FragmentTypeParent.t) ext.ext_args
782+
(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
785785
{id; locs; doc; args; res}

src/loader/cmti.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -214,7 +214,7 @@ let read_constructor_declaration_arguments env parent label_parent arg =
214214
let read_constructor_declaration env parent cd =
215215
let open TypeDecl.Constructor in
216216
let id = Ident_env.find_constructor_identifier env cd.cd_id in
217-
let container = (parent :> Identifier.FragmentTypeParent.t) in
217+
let container = (parent :> Identifier.FieldParent.t) in
218218
let label_container = (container :> Identifier.LabelParent.t) in
219219
let doc = Doc_attr.attached_no_tag label_container cd.cd_attributes in
220220
let args =
@@ -231,7 +231,7 @@ let read_type_kind env parent =
231231
let cstrs = List.map (read_constructor_declaration env parent) cstrs in
232232
Some (Variant cstrs)
233233
| Ttype_record lbls ->
234-
let parent = (parent :> Identifier.FragmentTypeParent.t) in
234+
let parent = (parent :> Identifier.FieldParent.t) in
235235
let label_parent = (parent :> Identifier.LabelParent.t) in
236236
let lbls =
237237
List.map (read_label_declaration env parent label_parent) lbls in
@@ -292,7 +292,7 @@ let read_extension_constructor env parent ext =
292292
let open Extension.Constructor in
293293
let id = Env.find_extension_identifier env ext.ext_id in
294294
let locs = None in
295-
let container = (parent : Identifier.Signature.t :> Identifier.FragmentTypeParent.t) in
295+
let container = (parent : Identifier.Signature.t :> Identifier.FieldParent.t) in
296296
let label_container = (container :> Identifier.LabelParent.t) in
297297
let doc = Doc_attr.attached_no_tag label_container ext.ext_attributes in
298298
match ext.ext_kind with
@@ -325,7 +325,7 @@ let read_exception env parent (ext : extension_constructor) =
325325
let open Exception in
326326
let id = Env.find_exception_identifier env ext.ext_id in
327327
let locs = None in
328-
let container = (parent : Identifier.Signature.t :> Identifier.FragmentTypeParent.t) in
328+
let container = (parent : Identifier.Signature.t :> Identifier.FieldParent.t) in
329329
let label_container = (container :> Identifier.LabelParent.t) in
330330
let doc = Doc_attr.attached_no_tag label_container ext.ext_attributes in
331331
match ext.ext_kind with

src/model/paths.ml

Lines changed: 14 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -166,7 +166,7 @@ module Identifier = struct
166166
| { iv = `Method (p, _); _ } | { iv = `InstanceVariable (p, _); _ } ->
167167
(p : class_signature :> label_parent)
168168
| { iv = `Constructor (p, _); _ } -> (p : datatype :> label_parent)
169-
| { iv = `Field (p, _); _ } -> (p : fragment_type_parent :> label_parent)
169+
| { iv = `Field (p, _); _ } -> (p : field_parent :> label_parent)
170170

171171
let label_parent n = label_parent_aux (n :> Id.non_src)
172172

@@ -217,9 +217,9 @@ module Identifier = struct
217217
type t_pv = Id.datatype_pv
218218
end
219219

220-
module FragmentTypeParent = struct
221-
type t = Paths_types.Identifier.fragment_type_parent
222-
type t_pv = Paths_types.Identifier.fragment_type_parent_pv
220+
module FieldParent = struct
221+
type t = Paths_types.Identifier.field_parent
222+
type t_pv = Paths_types.Identifier.field_parent_pv
223223
end
224224

225225
module LabelParent = struct
@@ -578,8 +578,8 @@ module Identifier = struct
578578
`Constructor (p, n))
579579

580580
let field :
581-
FragmentTypeParent.t * FieldName.t ->
582-
[> `Field of FragmentTypeParent.t * FieldName.t ] id =
581+
FieldParent.t * FieldName.t ->
582+
[> `Field of FieldParent.t * FieldName.t ] id =
583583
mk_parent FieldName.to_string "fld" (fun (p, n) -> `Field (p, n))
584584

585585
let extension :
@@ -992,14 +992,13 @@ module Reference = struct
992992
| `ClassType (sg, s) ->
993993
Identifier.Mk.class_type (parent_signature_identifier sg, s)
994994

995-
and parent_identifier :
996-
fragment_type_parent -> Identifier.FragmentTypeParent.t = function
995+
and field_parent_identifier : field_parent -> Identifier.FieldParent.t =
996+
function
997997
| `Identifier id -> id
998998
| (`Hidden _ | `Alias _ | `AliasModuleType _ | `Module _ | `ModuleType _)
999999
as sg ->
1000-
(parent_signature_identifier sg :> Identifier.FragmentTypeParent.t)
1001-
| `Type _ as t ->
1002-
(parent_type_identifier t :> Identifier.FragmentTypeParent.t)
1000+
(parent_signature_identifier sg :> Identifier.FieldParent.t)
1001+
| `Type _ as t -> (parent_type_identifier t :> Identifier.FieldParent.t)
10031002

10041003
and label_parent_identifier : label_parent -> Identifier.LabelParent.t =
10051004
function
@@ -1008,14 +1007,14 @@ module Reference = struct
10081007
(parent_class_signature_identifier c :> Identifier.LabelParent.t)
10091008
| ( `Hidden _ | `Alias _ | `AliasModuleType _ | `Module _ | `ModuleType _
10101009
| `Type _ ) as r ->
1011-
(parent_identifier r :> Identifier.LabelParent.t)
1010+
(field_parent_identifier r :> Identifier.LabelParent.t)
10121011

10131012
and identifier : t -> Identifier.t = function
10141013
| `Identifier id -> id
10151014
| ( `Alias _ | `AliasModuleType _ | `Module _ | `Hidden _ | `Type _
10161015
| `Class _ | `ClassType _ | `ModuleType _ ) as r ->
10171016
(label_parent_identifier r :> Identifier.t)
1018-
| `Field (p, n) -> Identifier.Mk.field (parent_identifier p, n)
1017+
| `Field (p, n) -> Identifier.Mk.field (field_parent_identifier p, n)
10191018
| `Constructor (s, n) ->
10201019
Identifier.Mk.constructor
10211020
((parent_type_identifier s :> Identifier.DataType.t), n)
@@ -1045,8 +1044,8 @@ module Reference = struct
10451044
type t = Paths_types.Resolved_reference.datatype
10461045
end
10471046

1048-
module FragmentTypeParent = struct
1049-
type t = Paths_types.Resolved_reference.fragment_type_parent
1047+
module FieldParent = struct
1048+
type t = Paths_types.Resolved_reference.field_parent
10501049
end
10511050

10521051
module LabelParent = struct

src/model/paths.mli

Lines changed: 7 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -79,9 +79,9 @@ module Identifier : sig
7979
type t = Id.datatype
8080
type t_pv = Id.datatype_pv
8181
end
82-
module FragmentTypeParent : sig
83-
type t = Id.fragment_type_parent
84-
type t_pv = Id.fragment_type_parent_pv
82+
module FieldParent : sig
83+
type t = Id.field_parent
84+
type t_pv = Id.field_parent_pv
8585
end
8686

8787
module FunctorResult : sig
@@ -294,8 +294,8 @@ module Identifier : sig
294294
[> `Constructor of DataType.t * ConstructorName.t ] id
295295

296296
val field :
297-
FragmentTypeParent.t * FieldName.t ->
298-
[> `Field of FragmentTypeParent.t * FieldName.t ] id
297+
FieldParent.t * FieldName.t ->
298+
[> `Field of FieldParent.t * FieldName.t ] id
299299

300300
val extension :
301301
Signature.t * ExtensionName.t ->
@@ -508,8 +508,8 @@ module rec Reference : sig
508508
type t = Paths_types.Resolved_reference.datatype
509509
end
510510

511-
module FragmentTypeParent : sig
512-
type t = Paths_types.Resolved_reference.fragment_type_parent
511+
module FieldParent : sig
512+
type t = Paths_types.Resolved_reference.field_parent
513513
end
514514

515515
module LabelParent : sig

src/model/paths_types.ml

Lines changed: 12 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -81,17 +81,16 @@ module Identifier = struct
8181
and datatype = datatype_pv id
8282
(** @canonical Odoc_model.Paths.Identifier.DataType.t *)
8383

84-
type fragment_type_parent_pv = [ signature_pv | datatype_pv ]
85-
(** @canonical Odoc_model.Paths.Identifier.FragmentTypeParent.t_pv *)
84+
type field_parent_pv = [ signature_pv | datatype_pv ]
85+
(** @canonical Odoc_model.Paths.Identifier.FieldParent.t_pv *)
8686

8787
(* fragment_type_parent in identifiers is for record fields parent. It’s type
8888
(for usual record fields) or [signature] for fields of inline records of
8989
extension constructor. *)
90-
and fragment_type_parent = fragment_type_parent_pv id
91-
(** @canonical Odoc_model.Paths.Identifier.FragmentTypeParent.t *)
90+
and field_parent = field_parent_pv id
91+
(** @canonical Odoc_model.Paths.Identifier.FieldParent.t *)
9292

93-
type label_parent_pv =
94-
[ fragment_type_parent_pv | page_pv | class_signature_pv ]
93+
type label_parent_pv = [ field_parent_pv | page_pv | class_signature_pv ]
9594
(** @canonical Odoc_model.Paths.Identifier.LabelParent.t_pv *)
9695

9796
and label_parent = label_parent_pv id
@@ -142,7 +141,7 @@ module Identifier = struct
142141
and constructor = constructor_pv id
143142
(** @canonical Odoc_model.Paths.Identifier.Constructor.t *)
144143

145-
type field_pv = [ `Field of fragment_type_parent * FieldName.t ]
144+
type field_pv = [ `Field of field_parent * FieldName.t ]
146145
(** @canonical Odoc_model.Paths.Identifier.Field.t_pv *)
147146

148147
and field = field_pv id
@@ -210,7 +209,7 @@ module Identifier = struct
210209
[ signature_pv
211210
| class_signature_pv
212211
| datatype_pv
213-
| fragment_type_parent_pv
212+
| field_parent_pv
214213
| label_parent_pv
215214
| module_pv
216215
| functor_parameter_pv
@@ -623,7 +622,7 @@ module rec Reference : sig
623622

624623
(* Parent of fields and constructor. Can be either a type or [signature] *)
625624
and fragment_type_parent =
626-
[ `Resolved of Resolved_reference.fragment_type_parent
625+
[ `Resolved of Resolved_reference.field_parent
627626
| `Root of string * tag_parent
628627
| `Dot of label_parent * string
629628
| `Module of signature * ModuleName.t
@@ -811,8 +810,8 @@ and Resolved_reference : sig
811810
(* fragment_type_parent in resolved references is for record fields parent.
812811
It’s type (for usual record fields) or [signature] for fields of inline
813812
records of extension constructor. *)
814-
and fragment_type_parent =
815-
[ `Identifier of Identifier.fragment_type_parent
813+
and field_parent =
814+
[ `Identifier of Identifier.field_parent
816815
| `Alias of Resolved_path.module_ * module_
817816
| `AliasModuleType of Resolved_path.module_type * module_type
818817
| `Module of signature * ModuleName.t
@@ -857,7 +856,7 @@ and Resolved_reference : sig
857856

858857
type field =
859858
[ `Identifier of Identifier.reference_field
860-
| `Field of fragment_type_parent * FieldName.t ]
859+
| `Field of field_parent * FieldName.t ]
861860
(** @canonical Odoc_model.Paths.Reference.Resolved.Field.t *)
862861

863862
type extension =
@@ -924,7 +923,7 @@ and Resolved_reference : sig
924923
| `ModuleType of signature * ModuleTypeName.t
925924
| `Type of signature * TypeName.t
926925
| `Constructor of datatype * ConstructorName.t
927-
| `Field of fragment_type_parent * FieldName.t
926+
| `Field of field_parent * FieldName.t
928927
| `Extension of signature * ExtensionName.t
929928
| `ExtensionDecl of signature * ExtensionName.t * ExtensionName.t
930929
| `Exception of signature * ExceptionName.t

src/xref2/env.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -301,7 +301,7 @@ let add_type (identifier : Identifier.Type.t) t env =
301301
and add_field env (field : TypeDecl.Field.t) =
302302
let ident =
303303
Paths.Identifier.Mk.field
304-
( (identifier :> Paths.Identifier.FragmentTypeParent.t),
304+
( (identifier :> Paths.Identifier.FieldParent.t),
305305
FieldName.make_std field.name )
306306
in
307307
add_to_elts Kind_Field ident (`Field (ident, field)) env

src/xref2/ident.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -141,7 +141,7 @@ module Of_Identifier = struct
141141
| `Type (_, n) -> `LType (n, i)
142142
| `CoreType _n -> failwith "Bad"
143143

144-
let parent : FragmentTypeParent.t -> parent =
144+
let field_parent : FieldParent.t -> parent =
145145
fun p ->
146146
match p with
147147
| { iv = #Signature.t_pv; _ } as s -> (signature s :> parent)
@@ -152,7 +152,7 @@ module Of_Identifier = struct
152152
match p with
153153
| { iv = #ClassSignature.t_pv; _ } as s ->
154154
(class_signature s :> label_parent)
155-
| { iv = #FragmentTypeParent.t_pv; _ } as s -> (parent s :> label_parent)
155+
| { iv = #FieldParent.t_pv; _ } as s -> (field_parent s :> label_parent)
156156
| { iv = `Page (_, n); _ } -> `LPage (n, fresh_int ())
157157
| { iv = `LeafPage (_, n); _ } -> `LLeafPage (n, fresh_int ())
158158

src/xref2/lang_of.ml

Lines changed: 11 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -712,7 +712,7 @@ and extension_constructor map parent c =
712712
doc = docs (parent :> Identifier.LabelParent.t) c.doc;
713713
args =
714714
type_decl_constructor_argument map
715-
(parent :> Identifier.FragmentTypeParent.t)
715+
(parent :> Identifier.FieldParent.t)
716716
c.args;
717717
res = Opt.map (type_expr map (parent :> Identifier.LabelParent.t)) c.res;
718718
}
@@ -769,15 +769,11 @@ and mty_substitution map identifier = function
769769
| TypeEq (frag, eqn) ->
770770
TypeEq
771771
( Path.type_fragment map frag,
772-
type_decl_equation map
773-
(identifier :> Identifier.FragmentTypeParent.t)
774-
eqn )
772+
type_decl_equation map (identifier :> Identifier.FieldParent.t) eqn )
775773
| TypeSubst (frag, eqn) ->
776774
TypeSubst
777775
( Path.type_fragment map frag,
778-
type_decl_equation map
779-
(identifier :> Identifier.FragmentTypeParent.t)
780-
eqn )
776+
type_decl_equation map (identifier :> Identifier.FieldParent.t) eqn )
781777
| ModuleTypeEq (frag, eqn) ->
782778
ModuleTypeEq
783779
(Path.module_type_fragment map frag, module_type_expr map identifier eqn)
@@ -894,7 +890,7 @@ and module_type_substitution :
894890

895891
and type_decl_constructor_argument :
896892
maps ->
897-
Paths.Identifier.FragmentTypeParent.t ->
893+
Paths.Identifier.FieldParent.t ->
898894
Component.TypeDecl.Constructor.argument ->
899895
Odoc_model.Lang.TypeDecl.Constructor.argument =
900896
fun map parent a ->
@@ -903,13 +899,11 @@ and type_decl_constructor_argument :
903899
Tuple (List.map (type_expr map (parent :> Identifier.LabelParent.t)) ls)
904900
| Record fs ->
905901
Record
906-
(List.map
907-
(type_decl_field map (parent :> Identifier.FragmentTypeParent.t))
908-
fs)
902+
(List.map (type_decl_field map (parent :> Identifier.FieldParent.t)) fs)
909903

910904
and type_decl_field :
911905
maps ->
912-
Identifier.FragmentTypeParent.t ->
906+
Identifier.FieldParent.t ->
913907
Component.TypeDecl.Field.t ->
914908
Odoc_model.Lang.TypeDecl.Field.t =
915909
fun map parent f ->
@@ -921,7 +915,7 @@ and type_decl_field :
921915
type_ = type_expr map (parent :> Identifier.LabelParent.t) f.type_;
922916
}
923917

924-
and type_decl_equation map (parent : Identifier.FragmentTypeParent.t)
918+
and type_decl_equation map (parent : Identifier.FieldParent.t)
925919
(eqn : Component.TypeDecl.Equation.t) : Odoc_model.Lang.TypeDecl.Equation.t
926920
=
927921
let parent = (parent :> Identifier.LabelParent.t) in
@@ -942,9 +936,7 @@ and type_decl map parent id (t : Component.TypeDecl.t) :
942936
id = identifier;
943937
locs = t.locs;
944938
equation =
945-
type_decl_equation map
946-
(parent :> Identifier.FragmentTypeParent.t)
947-
t.equation;
939+
type_decl_equation map (parent :> Identifier.FieldParent.t) t.equation;
948940
doc = docs (parent :> Identifier.LabelParent.t) t.doc;
949941
canonical = t.canonical;
950942
representation =
@@ -960,7 +952,7 @@ and type_decl_representation map id (t : Component.TypeDecl.Representation.t) :
960952
Record
961953
(List.map
962954
(type_decl_field map
963-
(id :> Odoc_model.Paths.Identifier.FragmentTypeParent.t))
955+
(id :> Odoc_model.Paths.Identifier.FieldParent.t))
964956
fs)
965957

966958
and type_decl_constructor :
@@ -977,9 +969,7 @@ and type_decl_constructor :
977969
id = identifier;
978970
doc = docs parent t.doc;
979971
args =
980-
type_decl_constructor_argument map
981-
(id :> Identifier.FragmentTypeParent.t)
982-
t.args;
972+
type_decl_constructor_argument map (id :> Identifier.FieldParent.t) t.args;
983973
res = Opt.map (type_expr map parent) t.res;
984974
}
985975

@@ -1072,7 +1062,7 @@ and exception_ map parent id (e : Component.Exception.t) :
10721062
doc = docs (parent :> Identifier.LabelParent.t) e.doc;
10731063
args =
10741064
type_decl_constructor_argument map
1075-
(parent :> Identifier.FragmentTypeParent.t)
1065+
(parent :> Identifier.FieldParent.t)
10761066
e.args;
10771067
res = Opt.map (type_expr map (parent :> Identifier.LabelParent.t)) e.res;
10781068
}

0 commit comments

Comments
 (0)