@@ -424,22 +424,6 @@ module Identifier = struct
424424 let compare = compare
425425 end
426426
427- module DataType = struct
428- type t = Id .path_datatype
429- type t_pv = Id .path_datatype_pv
430- let equal = equal
431- let hash = hash
432- let compare = compare
433- end
434-
435- module Constructor = struct
436- type t = Id .path_constructor
437- type t_pv = Id .constructor_pv
438- let equal = equal
439- let hash = hash
440- let compare = compare
441- end
442-
443427 module Value = struct
444428 type t = Id .path_value
445429 type t_pv = Id .value_pv
@@ -686,7 +670,6 @@ module Path = struct
686670 | `Type (p , _ ) -> inner (p : module_ :> any )
687671 | `Value (_ , t ) when Names.ValueName. is_internal t -> true
688672 | `Value (p , _ ) -> inner (p : module_ :> any )
689- | `Constructor (p , _ ) -> inner (p : datatype :> any )
690673 | `Class (p , _ ) -> inner (p : module_ :> any )
691674 | `ClassType (p , _ ) -> inner (p : module_ :> any )
692675 | `Alias (dest , `Resolved src ) ->
@@ -701,8 +684,6 @@ module Path = struct
701684 | `CanonicalModuleType (x , _ ) -> inner (x : module_type :> any )
702685 | `CanonicalType (_ , `Resolved _ ) -> false
703686 | `CanonicalType (x , _ ) -> inner (x : type_ :> any )
704- | `CanonicalDataType (_ , `Resolved _ ) -> false
705- | `CanonicalDataType (x , _ ) -> inner (x : datatype :> any )
706687 | `OpaqueModule m -> inner (m :> any )
707688 | `OpaqueModuleType mt -> inner (mt :> any )
708689 in
@@ -756,14 +737,6 @@ module Path = struct
756737 | `Alias (dest , _src ) -> parent_module_identifier dest
757738 | `OpaqueModule m -> parent_module_identifier m
758739
759- and parent_datatype_identifier :
760- Paths_types.Resolved_path. datatype -> Identifier.DataType. t = function
761- | `Identifier id ->
762- (id : Identifier.Path.DataType.t :> Identifier.DataType.t )
763- | `CanonicalDataType (_ , `Resolved p ) -> parent_datatype_identifier p
764- | `CanonicalDataType (p , _ ) -> parent_datatype_identifier p
765- | `Type (m , n ) -> Identifier.Mk. type_ (parent_module_identifier m, n)
766-
767740 module Module = struct
768741 type t = Paths_types.Resolved_path .module_
769742
@@ -779,14 +752,6 @@ module Path = struct
779752 type t = Paths_types.Resolved_path .type_
780753 end
781754
782- module DataType = struct
783- type t = Paths_types.Resolved_path .datatype
784- end
785-
786- module Constructor = struct
787- type t = Paths_types.Resolved_path .constructor
788- end
789-
790755 module Value = struct
791756 type t = Paths_types.Resolved_path .value
792757 end
@@ -805,8 +770,6 @@ module Path = struct
805770 | `Apply (m , _ ) -> identifier (m :> t )
806771 | `Type (m , n ) -> Identifier.Mk. type_ (parent_module_identifier m, n)
807772 | `Value (m , n ) -> Identifier.Mk. value (parent_module_identifier m, n)
808- | `Constructor (m , n ) ->
809- Identifier.Mk. constructor (parent_datatype_identifier m, n)
810773 | `ModuleType (m , n ) ->
811774 Identifier.Mk. module_type (parent_module_identifier m, n)
812775 | `Class (m , n ) -> Identifier.Mk. class_ (parent_module_identifier m, n)
@@ -826,8 +789,6 @@ module Path = struct
826789 | `CanonicalModuleType (p , _ ) -> identifier (p :> t )
827790 | `CanonicalType (_ , `Resolved p ) -> identifier (p :> t )
828791 | `CanonicalType (p , _ ) -> identifier (p :> t )
829- | `CanonicalDataType (_ , `Resolved p ) -> identifier (p :> t )
830- | `CanonicalDataType (p , _ ) -> identifier (p :> t )
831792 | `OpaqueModule m -> identifier (m :> t )
832793 | `OpaqueModuleType mt -> identifier (mt :> t )
833794
@@ -846,14 +807,6 @@ module Path = struct
846807 type t = Paths_types.Path .type_
847808 end
848809
849- module DataType = struct
850- type t = Paths_types.Path .datatype
851- end
852-
853- module Constructor = struct
854- type t = Paths_types.Path .constructor
855- end
856-
857810 module Value = struct
858811 type t = Paths_types.Path .value
859812 end
0 commit comments