We read every piece of feedback, and take your input very seriously.
To see all available qualifiers, see our documentation.
There was an error while loading. Please reload this page.
ClassType
Class
1 parent 6138d19 commit 5a411b1Copy full SHA for 5a411b1
src/document/generator.ml
@@ -284,7 +284,7 @@ module Make (Syntax : SYNTAX) = struct
284
| Module { documentation; _ } -> to_link documentation None
285
| ModuleType { documentation; _ } -> to_link documentation None
286
| Type { documentation; _ } -> to_link documentation None
287
- | Class { documentation; _ } -> to_link documentation None
+ | ClassType { documentation; _ } -> to_link documentation None
288
| Value { documentation; implementation } ->
289
to_link documentation implementation
290
| Constructor { documentation; _ } -> to_link documentation None
src/loader/implementation.ml
@@ -146,7 +146,7 @@ let postprocess_poses source_id poses uid_to_id uid_to_loc :
146
{ v with implementation = None },
147
loc )
148
| Module m, loc -> Some (Module { m with implementation = None }, loc)
149
- | Class m, loc -> Some (Class { m with implementation = None }, loc)
+ | ClassType m, loc -> Some (ClassType { m with implementation = None }, loc)
150
| ModuleType m, loc ->
151
Some (ModuleType { m with implementation = None }, loc)
152
| Type m, loc -> Some (Type { m with implementation = None }, loc)
@@ -193,7 +193,7 @@ let postprocess_poses source_id poses uid_to_id uid_to_loc :
193
in
194
(Value { v with implementation }, loc)
195
| Module m, loc -> (Module m, loc)
196
- | Class m, loc -> (Class m, loc)
+ | ClassType m, loc -> (ClassType m, loc)
197
| ModuleType m, loc -> (ModuleType m, loc)
198
| Type m, loc -> (Type m, loc)
199
| Constructor m, loc -> (Constructor m, loc))
src/loader/occurrences.ml
@@ -9,7 +9,7 @@ module Global_analysis = struct
9
| Definition of Ident.t
10
| Value of (Odoc_model.Paths.Path.Value.t, value_implementation) jump_to
11
| Module of (Odoc_model.Paths.Path.Module.t, none) jump_to
12
- | Class of (Odoc_model.Paths.Path.ClassType.t, none) jump_to
+ | ClassType of (Odoc_model.Paths.Path.ClassType.t, none) jump_to
13
| ModuleType of (Odoc_model.Paths.Path.ModuleType.t, none) jump_to
14
| Type of (Odoc_model.Paths.Path.Type.t, none) jump_to
15
| Constructor of (Odoc_model.Paths.Path.Constructor.t, none) jump_to
@@ -154,7 +154,7 @@ module Global_analysis = struct
154
let implementation = None in
155
let documentation = childpath_of_path p in
156
poses :=
157
- (Class { implementation; documentation }, pos_of_loc cltyp_loc)
+ (ClassType { implementation; documentation }, pos_of_loc cltyp_loc)
158
:: !poses
159
| _ -> ()
160
src/model/lang.ml
@@ -27,7 +27,7 @@ module Source_info = struct
27
| Definition of Paths.Identifier.SourceLocation.t
28
| Value of (Path.Value.t, Paths.Identifier.SourceLocation.t) jump_to
29
| Module of (Path.Module.t, none) jump_to
30
- | Class of (Path.ClassType.t, none) jump_to
+ | ClassType of (Path.ClassType.t, none) jump_to
31
| ModuleType of (Path.ModuleType.t, none) jump_to
32
| Type of (Path.Type.t, none) jump_to
33
| Constructor of (Path.Constructor.t, none) jump_to
src/odoc/occurrences.ml
@@ -130,7 +130,7 @@ let count ~dst ~warnings_options:_ directories =
130
incr htbl p Odoc_model.Paths.Path.((p' : Module.t :> t))
131
| Value ({documentation = Some (`Resolved p as p') ; _}), _ ->
132
incr htbl p Odoc_model.Paths.Path.((p' : Value.t :> t))
133
- | Class ({documentation = Some (`Resolved p as p') ; _}), _ ->
+ | ClassType ({documentation = Some (`Resolved p as p') ; _}), _ ->
134
incr htbl p Odoc_model.Paths.Path.((p' : ClassType.t :> t))
135
| ModuleType ({documentation = Some (`Resolved p as p') ; _}), _ ->
136
incr htbl p Odoc_model.Paths.Path.((p' : ModuleType.t :> t))
0 commit comments