Skip to content

Commit 5a411b1

Browse files
committed
Occurrences: fix ClassType wrongly named Class
Signed-off-by: Paul-Elliot <peada@free.fr>
1 parent 6138d19 commit 5a411b1

File tree

5 files changed

+7
-7
lines changed

5 files changed

+7
-7
lines changed

src/document/generator.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -284,7 +284,7 @@ module Make (Syntax : SYNTAX) = struct
284284
| Module { documentation; _ } -> to_link documentation None
285285
| ModuleType { documentation; _ } -> to_link documentation None
286286
| Type { documentation; _ } -> to_link documentation None
287-
| Class { documentation; _ } -> to_link documentation None
287+
| ClassType { documentation; _ } -> to_link documentation None
288288
| Value { documentation; implementation } ->
289289
to_link documentation implementation
290290
| Constructor { documentation; _ } -> to_link documentation None

src/loader/implementation.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -146,7 +146,7 @@ let postprocess_poses source_id poses uid_to_id uid_to_loc :
146146
{ v with implementation = None },
147147
loc )
148148
| Module m, loc -> Some (Module { m with implementation = None }, loc)
149-
| Class m, loc -> Some (Class { m with implementation = None }, loc)
149+
| ClassType m, loc -> Some (ClassType { m with implementation = None }, loc)
150150
| ModuleType m, loc ->
151151
Some (ModuleType { m with implementation = None }, loc)
152152
| 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 :
193193
in
194194
(Value { v with implementation }, loc)
195195
| Module m, loc -> (Module m, loc)
196-
| Class m, loc -> (Class m, loc)
196+
| ClassType m, loc -> (ClassType m, loc)
197197
| ModuleType m, loc -> (ModuleType m, loc)
198198
| Type m, loc -> (Type m, loc)
199199
| Constructor m, loc -> (Constructor m, loc))

src/loader/occurrences.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ module Global_analysis = struct
99
| Definition of Ident.t
1010
| Value of (Odoc_model.Paths.Path.Value.t, value_implementation) jump_to
1111
| Module of (Odoc_model.Paths.Path.Module.t, none) jump_to
12-
| Class of (Odoc_model.Paths.Path.ClassType.t, none) jump_to
12+
| ClassType of (Odoc_model.Paths.Path.ClassType.t, none) jump_to
1313
| ModuleType of (Odoc_model.Paths.Path.ModuleType.t, none) jump_to
1414
| Type of (Odoc_model.Paths.Path.Type.t, none) jump_to
1515
| Constructor of (Odoc_model.Paths.Path.Constructor.t, none) jump_to
@@ -154,7 +154,7 @@ module Global_analysis = struct
154154
let implementation = None in
155155
let documentation = childpath_of_path p in
156156
poses :=
157-
(Class { implementation; documentation }, pos_of_loc cltyp_loc)
157+
(ClassType { implementation; documentation }, pos_of_loc cltyp_loc)
158158
:: !poses
159159
| _ -> ()
160160

src/model/lang.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ module Source_info = struct
2727
| Definition of Paths.Identifier.SourceLocation.t
2828
| Value of (Path.Value.t, Paths.Identifier.SourceLocation.t) jump_to
2929
| Module of (Path.Module.t, none) jump_to
30-
| Class of (Path.ClassType.t, none) jump_to
30+
| ClassType of (Path.ClassType.t, none) jump_to
3131
| ModuleType of (Path.ModuleType.t, none) jump_to
3232
| Type of (Path.Type.t, none) jump_to
3333
| Constructor of (Path.Constructor.t, none) jump_to

src/odoc/occurrences.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -130,7 +130,7 @@ let count ~dst ~warnings_options:_ directories =
130130
incr htbl p Odoc_model.Paths.Path.((p' : Module.t :> t))
131131
| Value ({documentation = Some (`Resolved p as p') ; _}), _ ->
132132
incr htbl p Odoc_model.Paths.Path.((p' : Value.t :> t))
133-
| Class ({documentation = Some (`Resolved p as p') ; _}), _ ->
133+
| ClassType ({documentation = Some (`Resolved p as p') ; _}), _ ->
134134
incr htbl p Odoc_model.Paths.Path.((p' : ClassType.t :> t))
135135
| ModuleType ({documentation = Some (`Resolved p as p') ; _}), _ ->
136136
incr htbl p Odoc_model.Paths.Path.((p' : ModuleType.t :> t))

0 commit comments

Comments
 (0)