Skip to content

Commit 831dc84

Browse files
panglesdjonludlam
authored andcommitted
Revert "Adding datatype and constructor to lang model"
This reverts commit 5826eb1.
1 parent 559f761 commit 831dc84

File tree

6 files changed

+0
-114
lines changed

6 files changed

+0
-114
lines changed

src/document/url.ml

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,6 @@ let render_path : Odoc_model.Paths.Path.t -> string =
3333
| `CanonicalModuleType (p, _) -> render_resolved (p :> t)
3434
| `CanonicalType (_, `Resolved p) -> render_resolved (p :> t)
3535
| `CanonicalType (p, _) -> render_resolved (p :> t)
36-
| `CanonicalDataType (_, `Resolved p) -> render_resolved (p :> t)
37-
| `CanonicalDataType (p, _) -> render_resolved (p :> t)
3836
| `Apply (rp, p) ->
3937
render_resolved (rp :> t)
4038
^ "("
@@ -44,8 +42,6 @@ let render_path : Odoc_model.Paths.Path.t -> string =
4442
render_resolved (p :> t) ^ "." ^ ModuleTypeName.to_string s
4543
| `Type (p, s) -> render_resolved (p :> t) ^ "." ^ TypeName.to_string s
4644
| `Value (p, s) -> render_resolved (p :> t) ^ "." ^ ValueName.to_string s
47-
| `Constructor (p, s) ->
48-
render_resolved (p :> t) ^ "." ^ ConstructorName.to_string s
4945
| `Class (p, s) -> render_resolved (p :> t) ^ "." ^ ClassName.to_string s
5046
| `ClassType (p, s) ->
5147
render_resolved (p :> t) ^ "." ^ ClassTypeName.to_string s

src/model/paths.ml

Lines changed: 0 additions & 47 deletions
Original file line numberDiff line numberDiff line change
@@ -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

src/model/paths.mli

Lines changed: 0 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -182,12 +182,6 @@ module Identifier : sig
182182
module Type :
183183
IdSig with type t = Id.path_type and type t_pv = Id.path_type_pv
184184

185-
module DataType :
186-
IdSig with type t = Id.path_datatype and type t_pv = Id.path_datatype_pv
187-
188-
module Constructor :
189-
IdSig with type t = Id.path_constructor and type t_pv = Id.constructor_pv
190-
191185
module Value : IdSig with type t = Id.path_value and type t_pv = Id.value_pv
192186

193187
module ClassType :
@@ -372,14 +366,6 @@ module rec Path : sig
372366
(* val identifier : t -> Identifier.Path.Type.t *)
373367
end
374368

375-
module DataType : sig
376-
type t = Paths_types.Resolved_path.datatype
377-
end
378-
379-
module Constructor : sig
380-
type t = Paths_types.Resolved_path.constructor
381-
end
382-
383369
module Value : sig
384370
type t = Paths_types.Resolved_path.value
385371
end
@@ -413,14 +399,6 @@ module rec Path : sig
413399
type t = Paths_types.Path.type_
414400
end
415401

416-
module DataType : sig
417-
type t = Paths_types.Path.datatype
418-
end
419-
420-
module Constructor : sig
421-
type t = Paths_types.Path.constructor
422-
end
423-
424402
module Value : sig
425403
type t = Paths_types.Path.value
426404
end

src/model/paths_types.ml

Lines changed: 0 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -259,14 +259,6 @@ module Identifier = struct
259259
and path_type = path_type_pv id
260260
(** @canonical Odoc_model.Paths.Identifier.Path.Type.t *)
261261

262-
type path_datatype_pv = type_pv
263-
(** @canonical Odoc_model.Paths.Identifier.Path.DataType.t_pv *)
264-
265-
and path_datatype = path_datatype_pv id
266-
(** @canonical Odoc_model.Paths.Identifier.Path.DataType.t *)
267-
268-
type path_constructor = constructor
269-
270262
type path_value = value
271263

272264
type path_class_type_pv = [ class_pv | class_type_pv ]
@@ -342,16 +334,6 @@ module rec Path : sig
342334
| `Dot of module_ * string ]
343335
(** @canonical Odoc_model.Paths.Path.Type.t *)
344336

345-
type datatype =
346-
[ `Resolved of Resolved_path.datatype
347-
| `Identifier of Identifier.path_datatype * bool
348-
| `Dot of module_ * string ]
349-
(** @canonical Odoc_model.Paths.Path.DataType.t *)
350-
351-
type constructor =
352-
[ `Resolved of Resolved_path.constructor | `Dot of datatype * string ]
353-
(** @canonical Odoc_model.Paths.Path.Constructor.t *)
354-
355337
type value =
356338
[ `Resolved of Resolved_path.value
357339
| `Identifier of Identifier.path_value * bool
@@ -404,15 +386,6 @@ and Resolved_path : sig
404386
| `ClassType of module_ * ClassTypeName.t ]
405387
(** @canonical Odoc_model.Paths.Path.Resolved.Type.t *)
406388

407-
type datatype =
408-
[ `Identifier of Identifier.datatype
409-
| `CanonicalDataType of datatype * Path.datatype
410-
| `Type of module_ * TypeName.t ]
411-
(** @canonical Odoc_model.Paths.Path.Resolved.DataType.t *)
412-
413-
type constructor = [ `Constructor of datatype * ConstructorName.t ]
414-
(** @canonical Odoc_model.Paths.Path.Resolved.Constructor.t *)
415-
416389
type value =
417390
[ `Identifier of Identifier.path_value | `Value of module_ * ValueName.t ]
418391
(** @canonical Odoc_model.Paths.Path.Resolved.Value.t *)
@@ -437,9 +410,7 @@ and Resolved_path : sig
437410
| `SubstT of module_type * module_type
438411
| `OpaqueModuleType of module_type
439412
| `CanonicalType of type_ * Path.type_
440-
| `CanonicalDataType of datatype * Path.datatype
441413
| `Type of module_ * TypeName.t
442-
| `Constructor of datatype * ConstructorName.t
443414
| `Class of module_ * ClassName.t
444415
| `ClassType of module_ * ClassTypeName.t
445416
| `Class of module_ * ClassName.t

src/model_desc/paths_desc.ml

Lines changed: 0 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -262,21 +262,11 @@ module General_paths = struct
262262
( "`CanonicalType",
263263
((x1 :> rp), (x2 :> p)),
264264
Pair (resolved_path, path) )
265-
| `CanonicalDataType (x1, x2) ->
266-
C
267-
( "`CanonicalDataType",
268-
((x1 :> rp), (x2 :> p)),
269-
Pair (resolved_path, path) )
270265
| `OpaqueModuleType x -> C ("`OpaqueModuleType", (x :> rp), resolved_path)
271266
| `Type (x1, x2) ->
272267
C ("`Type", ((x1 :> rp), x2), Pair (resolved_path, Names.typename))
273268
| `Value (x1, x2) ->
274269
C ("`Value", ((x1 :> rp), x2), Pair (resolved_path, Names.valuename))
275-
| `Constructor (x1, x2) ->
276-
C
277-
( "`Constructor",
278-
((x1 :> rp), x2),
279-
Pair (resolved_path, Names.constructorname) )
280270
| `Class (x1, x2) ->
281271
C ("`Class", ((x1 :> rp), x2), Pair (resolved_path, Names.classname))
282272
| `ClassType (x1, x2) ->

test/xref2/lib/common.cppo.ml

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -565,13 +565,11 @@ module LangUtils = struct
565565
| `ModuleType (p, mt) -> Format.fprintf ppf "%a.%s" resolved_path (cast p) (Odoc_model.Names.ModuleTypeName.to_string mt)
566566
| `Type (p, t) -> Format.fprintf ppf "%a.%s" resolved_path (cast p) (Odoc_model.Names.TypeName.to_string t)
567567
| `Value (p, t) -> Format.fprintf ppf "%a.%s" resolved_path (cast p) (Odoc_model.Names.ValueName.to_string t)
568-
| `Constructor (p, t) -> Format.fprintf ppf "%a.%s" resolved_path (cast p) (Odoc_model.Names.ConstructorName.to_string t)
569568
| `OpaqueModule m -> Format.fprintf ppf "opaquemodule(%a)" resolved_path (cast m)
570569
| `OpaqueModuleType m -> Format.fprintf ppf "opaquemoduletype(%a)" resolved_path (cast m)
571570
| `SubstT (_, _)
572571
| `CanonicalModuleType (_, _)
573572
| `CanonicalType (_, _)
574-
| `CanonicalDataType (_, _)
575573
| `Class (_, _)
576574
| `ClassType (_, _)
577575
| `Hidden _

0 commit comments

Comments
 (0)