Skip to content

Commit 57e158e

Browse files
panglesdjonludlam
authored andcommitted
Remove support for class types
Signed-off-by: Paul-Elliot <[email protected]>
1 parent 7770861 commit 57e158e

File tree

10 files changed

+8
-47
lines changed

10 files changed

+8
-47
lines changed

src/document/generator.ml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -288,7 +288,6 @@ module Make (Syntax : SYNTAX) = struct
288288
| Module v -> to_link v
289289
| ModuleType v -> to_link v
290290
| Type v -> to_link v
291-
| ClassType v -> to_link v
292291
| Value v -> to_link v
293292

294293
let source id syntax_info infos source_code =

src/loader/implementation.ml

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -320,10 +320,6 @@ let process_occurrences env poses loc_to_id local_ident_to_loc =
320320
process p Ident_env.Path.read_module
321321
|> Option.iter @@ fun l ->
322322
AnnotHashtbl.replace occ_tbl (Module l, pos_of_loc loc) ()
323-
| ClassType p, loc ->
324-
process p Ident_env.Path.read_class_type
325-
|> Option.iter @@ fun l ->
326-
AnnotHashtbl.replace occ_tbl (ClassType l, pos_of_loc loc) ()
327323
| ModuleType p, loc ->
328324
process p Ident_env.Path.read_module_type
329325
|> Option.iter @@ fun l ->

src/loader/typedtree_traverse.ml

Lines changed: 0 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@ module Analysis = struct
55
| LocalDefinition of Ident.t
66
| Value of Path.t
77
| Module of Path.t
8-
| ClassType of Path.t
98
| ModuleType of Path.t
109
| Type of Path.t
1110

@@ -53,13 +52,6 @@ module Analysis = struct
5352
poses := (Module p, mod_loc) :: !poses
5453
| _ -> ()
5554

56-
let class_type poses cltyp =
57-
match cltyp with
58-
| { Typedtree.cltyp_desc = Tcty_constr (p, _, _); cltyp_loc; _ }
59-
when not cltyp_loc.loc_ghost ->
60-
poses := (ClassType p, cltyp_loc) :: !poses
61-
| _ -> ()
62-
6355
let module_type poses mty_expr =
6456
match mty_expr with
6557
| { Typedtree.mty_desc = Tmty_ident (p, _); mty_loc; _ }
@@ -98,10 +90,6 @@ let of_cmt env structure =
9890
Analysis.module_type poses mty;
9991
iter.module_type iterator mty
10092
in
101-
let class_type iterator cl_type =
102-
Analysis.class_type poses cl_type;
103-
iter.class_type iterator cl_type
104-
in
10593
let module_binding iterator mb =
10694
Analysis.module_binding env poses mb;
10795
iter.module_binding iterator mb
@@ -114,7 +102,6 @@ let of_cmt env structure =
114102
module_expr;
115103
typ;
116104
module_type;
117-
class_type;
118105
module_binding;
119106
}
120107
in

src/model/lang.ml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,6 @@ module Source_info = struct
3131
| Definition of Paths.Identifier.SourceLocation.t
3232
| Value of Path.Value.t jump_to
3333
| Module of Path.Module.t jump_to
34-
| ClassType of Path.ClassType.t jump_to
3534
| ModuleType of Path.ModuleType.t jump_to
3635
| Type of Path.Type.t jump_to
3736

src/odoc/occurrences.ml

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -136,8 +136,6 @@ let count ~dst ~warnings_options:_ directories include_hidden =
136136
_ ) ->
137137
incr htbl p
138138
| Value { documentation = Some (`Resolved p); _ }, _ -> incr htbl p
139-
| ClassType { documentation = Some (`Resolved p); _ }, _ ->
140-
incr htbl p
141139
| ModuleType { documentation = Some (`Resolved p); _ }, _ ->
142140
incr htbl p
143141
| Type { documentation = Some (`Resolved p); _ }, _ -> incr htbl p

src/xref2/compile.ml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -91,7 +91,6 @@ and source_info_infos env infos =
9191
| Module v -> Module (map_doc (module_path env) v)
9292
| ModuleType v -> ModuleType (map_doc (module_type_path env) v)
9393
| Type v -> Type (map_doc (type_path env) v)
94-
| ClassType v -> ClassType (map_doc (class_type_path env) v)
9594
| Definition _ as d -> d
9695
in
9796
(v, pos))

src/xref2/link.ml

Lines changed: 0 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -421,11 +421,6 @@ let rec unit env t =
421421
(jump_to v
422422
(Shape_tools.lookup_type_path env)
423423
(type_path env))
424-
| ClassType v ->
425-
ClassType
426-
(jump_to v
427-
(Shape_tools.lookup_class_type_path env)
428-
(class_type_path env))
429424
| i -> i
430425
in
431426
(info, pos))

test/occurrences/double_wrapped.t/a.ml

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -7,5 +7,3 @@ module type M = sig end
77
let ( ||> ) x y = x + y
88

99
let _ = x + x
10-
11-
class ct = object end

test/occurrences/double_wrapped.t/b.ml

Lines changed: 0 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -13,7 +13,3 @@ module type Y = A.M
1313
let _ =
1414
let open A in
1515
1 ||> 2
16-
17-
let ob = new A.ct
18-
19-
class ct : A.ct = A.ct

test/occurrences/double_wrapped.t/run.t

Lines changed: 8 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -16,8 +16,6 @@ occurrences information.
1616
$ odoc compile --count-occurrences -I . main__A.cmt
1717
$ odoc compile --count-occurrences -I . main__C.cmt
1818
$ odoc compile --count-occurrences -I . main__B.cmt
19-
File "main__B.cmt":
20-
Warning: Failed to compile expansion for class (root Main__B).ct
2119
$ odoc compile --count-occurrences -I . main__.cmt
2220
$ odoc compile --count-occurrences -I . main.cmt
2321

@@ -70,11 +68,10 @@ A only uses "persistent" values: one it defines itself.
7068

7169
"Aliased" values are not counted since they become persistent
7270
$ occurrences_print occurrences-main__B.odoc | sort
73-
Main was used directly 0 times and indirectly 8 times
74-
Main.A was used directly 2 times and indirectly 6 times
71+
Main was used directly 0 times and indirectly 7 times
72+
Main.A was used directly 2 times and indirectly 5 times
7573
Main.A.(||>) was used directly 1 times and indirectly 0 times
7674
Main.A.M was used directly 2 times and indirectly 0 times
77-
Main.A.ct was used directly 1 times and indirectly 0 times
7875
Main.A.t was used directly 1 times and indirectly 0 times
7976
Main.A.x was used directly 1 times and indirectly 0 times
8077

@@ -95,11 +92,10 @@ Now we can merge all tables
9592

9693
$ occurrences_print occurrences-aggregated.odoc | sort > all_merged
9794
$ cat all_merged
98-
Main was used directly 0 times and indirectly 12 times
99-
Main.A was used directly 4 times and indirectly 7 times
95+
Main was used directly 0 times and indirectly 11 times
96+
Main.A was used directly 4 times and indirectly 6 times
10097
Main.A.(||>) was used directly 1 times and indirectly 0 times
10198
Main.A.M was used directly 2 times and indirectly 0 times
102-
Main.A.ct was used directly 1 times and indirectly 0 times
10399
Main.A.t was used directly 1 times and indirectly 0 times
104100
Main.A.x was used directly 2 times and indirectly 0 times
105101
Main.B was used directly 1 times and indirectly 0 times
@@ -114,11 +110,10 @@ We can also include hidden ids:
114110

115111
$ odoc count-occurrences -I main__B -o occurrences-b.odoc --include-hidden
116112
$ occurrences_print occurrences-b.odoc | sort
117-
Main was used directly 0 times and indirectly 8 times
118-
Main.A was used directly 2 times and indirectly 6 times
113+
Main was used directly 0 times and indirectly 7 times
114+
Main.A was used directly 2 times and indirectly 5 times
119115
Main.A.(||>) was used directly 1 times and indirectly 0 times
120116
Main.A.M was used directly 2 times and indirectly 0 times
121-
Main.A.ct was used directly 1 times and indirectly 0 times
122117
Main.A.t was used directly 1 times and indirectly 0 times
123118
Main.A.x was used directly 1 times and indirectly 0 times
124119
Main__ was used directly 0 times and indirectly 2 times
@@ -127,11 +122,10 @@ We can also include hidden ids:
127122

128123
$ odoc count-occurrences -I . -o occurrences-all.odoc --include-hidden
129124
$ occurrences_print occurrences-all.odoc | sort
130-
Main was used directly 0 times and indirectly 12 times
131-
Main.A was used directly 4 times and indirectly 7 times
125+
Main was used directly 0 times and indirectly 11 times
126+
Main.A was used directly 4 times and indirectly 6 times
132127
Main.A.(||>) was used directly 1 times and indirectly 0 times
133128
Main.A.M was used directly 2 times and indirectly 0 times
134-
Main.A.ct was used directly 1 times and indirectly 0 times
135129
Main.A.t was used directly 1 times and indirectly 0 times
136130
Main.A.x was used directly 2 times and indirectly 0 times
137131
Main.B was used directly 1 times and indirectly 0 times

0 commit comments

Comments
 (0)