@@ -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 : 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 Parent = struct
221- type t = Id .parent
222- type t_pv = Id .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
@@ -572,13 +572,14 @@ module Identifier = struct
572572 mk_fresh (fun s -> s) " coret" (fun s -> `CoreType (TypeName. make_std s))
573573
574574 let constructor :
575- Type .t * ConstructorName. t ->
576- [> `Constructor of Type .t * ConstructorName. t ] id =
575+ DataType .t * ConstructorName. t ->
576+ [> `Constructor of DataType .t * ConstructorName. t ] id =
577577 mk_parent ConstructorName. to_string " ctor" (fun (p , n ) ->
578578 `Constructor (p, n))
579579
580580 let field :
581- Parent. t * FieldName. t -> [> `Field of Parent. t * FieldName. t ] id =
581+ FieldParent. t * FieldName. t ->
582+ [> `Field of FieldParent. t * FieldName. t ] id =
582583 mk_parent FieldName. to_string " fld" (fun (p , n ) -> `Field (p, n))
583584
584585 let extension :
@@ -991,30 +992,32 @@ module Reference = struct
991992 | `ClassType (sg , s ) ->
992993 Identifier.Mk. class_type (parent_signature_identifier sg, s)
993994
994- and parent_identifier : parent -> Identifier.Parent.t = function
995+ and field_parent_identifier : field_parent -> Identifier.FieldParent.t =
996+ function
995997 | `Identifier id -> id
996998 | (`Hidden _ | `Alias _ | `AliasModuleType _ | `Module _ | `ModuleType _)
997999 as sg ->
998- (parent_signature_identifier sg :> Identifier.Parent.t )
999- | `Type _ as t -> (parent_type_identifier t :> Identifier.Parent.t )
1000- | (`Class _ | `ClassType _ ) as c ->
1001- (parent_class_signature_identifier c :> Identifier.Parent.t )
1000+ (parent_signature_identifier sg :> Identifier.FieldParent.t )
1001+ | `Type _ as t -> (parent_type_identifier t :> Identifier.FieldParent.t )
10021002
10031003 and label_parent_identifier : label_parent -> Identifier.LabelParent.t =
10041004 function
10051005 | `Identifier id -> id
1006+ | (`Class _ | `ClassType _ ) as c ->
1007+ (parent_class_signature_identifier c :> Identifier.LabelParent.t )
10061008 | ( `Hidden _ | `Alias _ | `AliasModuleType _ | `Module _ | `ModuleType _
1007- | `Type _ | `Class _ | `ClassType _ ) as r ->
1008- (parent_identifier r :> Identifier.LabelParent.t )
1009+ | `Type _ ) as r ->
1010+ (field_parent_identifier r :> Identifier.LabelParent.t )
10091011
10101012 and identifier : t -> Identifier.t = function
10111013 | `Identifier id -> id
10121014 | ( `Alias _ | `AliasModuleType _ | `Module _ | `Hidden _ | `Type _
10131015 | `Class _ | `ClassType _ | `ModuleType _ ) as r ->
10141016 (label_parent_identifier r :> Identifier.t )
1015- | `Field (p , n ) -> Identifier.Mk. field (parent_identifier p, n)
1017+ | `Field (p , n ) -> Identifier.Mk. field (field_parent_identifier p, n)
10161018 | `Constructor (s , n ) ->
1017- Identifier.Mk. constructor (parent_type_identifier s, n)
1019+ Identifier.Mk. constructor
1020+ ((parent_type_identifier s :> Identifier.DataType.t ), n)
10181021 | `Extension (p , q ) ->
10191022 Identifier.Mk. extension (parent_signature_identifier p, q)
10201023 | `ExtensionDecl (p , q , r ) ->
@@ -1041,8 +1044,8 @@ module Reference = struct
10411044 type t = Paths_types.Resolved_reference .datatype
10421045 end
10431046
1044- module Parent = struct
1045- type t = Paths_types.Resolved_reference .parent
1047+ module FieldParent = struct
1048+ type t = Paths_types.Resolved_reference .field_parent
10461049 end
10471050
10481051 module LabelParent = struct
@@ -1126,8 +1129,8 @@ module Reference = struct
11261129 type t = Paths_types.Reference .datatype
11271130 end
11281131
1129- module Parent = struct
1130- type t = Paths_types.Reference .parent
1132+ module FragmentTypeParent = struct
1133+ type t = Paths_types.Reference .fragment_type_parent
11311134 end
11321135
11331136 module LabelParent = struct
0 commit comments