Skip to content

Commit a5c1513

Browse files
committed
PR review updates
1 parent 68ead12 commit a5c1513

File tree

15 files changed

+103
-92
lines changed

15 files changed

+103
-92
lines changed

src/document/url.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -29,10 +29,10 @@ let render_path : Odoc_model.Paths.Path.t -> string =
2929
| `Module (p, s) -> render_resolved (p :> t) ^ "." ^ ModuleName.to_string s
3030
| `Canonical (_, `Resolved p) -> render_resolved (p :> t)
3131
| `Canonical (p, _) -> render_resolved (p :> t)
32-
| `CanonicalT (_, `Resolved p) -> render_resolved (p :> t)
33-
| `CanonicalT (p, _) -> render_resolved (p :> t)
34-
| `CanonicalTy (_, `Resolved p) -> render_resolved (p :> t)
35-
| `CanonicalTy (p, _) -> render_resolved (p :> t)
32+
| `CanonicalModuleType (_, `Resolved p) -> render_resolved (p :> t)
33+
| `CanonicalModuleType (p, _) -> render_resolved (p :> t)
34+
| `CanonicalType (_, `Resolved p) -> render_resolved (p :> t)
35+
| `CanonicalType (p, _) -> render_resolved (p :> t)
3636
| `Apply (rp, p) ->
3737
render_resolved (rp :> t)
3838
^ "("

src/model/error.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -8,10 +8,6 @@ type t =
88
[ `With_full_location of full_location_payload
99
| `With_filename_only of filename_only_payload ]
1010

11-
type 'a with_warnings = { value : 'a; warnings : t list }
12-
13-
type warning_accumulator = t list ref
14-
1511
let kasprintf k fmt =
1612
Format.(kfprintf (fun _ -> k (flush_str_formatter ())) str_formatter fmt)
1713

@@ -54,6 +50,10 @@ let to_exception = function Ok v -> v | Error error -> raise_exception error
5450

5551
let catch f = try Ok (f ()) with Conveyed_by_exception error -> Error error
5652

53+
type 'a with_warnings = { value : 'a; warnings : t list }
54+
55+
type warning_accumulator = t list ref
56+
5757
let accumulate_warnings f =
5858
let warnings = ref [] in
5959
let value = f warnings in

src/model/error.mli

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,5 @@
11
type t
22

3-
type 'a with_warnings = { value : 'a; warnings : t list }
4-
5-
type warning_accumulator
6-
73
val make :
84
?suggestion:string ->
95
('a, Format.formatter, unit, Location_.span -> t) format4 ->
@@ -20,6 +16,10 @@ val to_exception : ('a, t) Result.result -> 'a
2016

2117
val catch : (unit -> 'a) -> ('a, t) Result.result
2218

19+
type 'a with_warnings = { value : 'a; warnings : t list }
20+
21+
type warning_accumulator
22+
2323
val accumulate_warnings : (warning_accumulator -> 'a) -> 'a with_warnings
2424

2525
val warning : warning_accumulator -> t -> unit

src/model/paths.ml

Lines changed: 18 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -566,10 +566,10 @@ module Path = struct
566566
| `Alias (p1, p2) ->
567567
inner (p1 : module_ :> any) && inner (p2 : module_ :> any)
568568
| `SubstT (p1, p2) -> inner (p1 :> any) || inner (p2 :> any)
569-
| `CanonicalT (_, `Resolved _) -> false
570-
| `CanonicalT (x, _) -> inner (x : module_type :> any)
571-
| `CanonicalTy (_, `Resolved _) -> false
572-
| `CanonicalTy (x, _) -> inner (x : type_ :> any)
569+
| `CanonicalModuleType (_, `Resolved _) -> false
570+
| `CanonicalModuleType (x, _) -> inner (x : module_type :> any)
571+
| `CanonicalType (_, `Resolved _) -> false
572+
| `CanonicalType (x, _) -> inner (x : type_ :> any)
573573
| `OpaqueModule m -> inner (m :> any)
574574
| `OpaqueModuleType mt -> inner (mt :> any)
575575
in
@@ -597,8 +597,8 @@ module Path = struct
597597
(id : Identifier.ModuleType.t :> Identifier.Signature.t)
598598
| `ModuleType (m, n) -> `ModuleType (parent_module_identifier m, n)
599599
| `SubstT (m, _n) -> parent_module_type_identifier m
600-
| `CanonicalT (_, `Resolved p) -> parent_module_type_identifier p
601-
| `CanonicalT (p, _) -> parent_module_type_identifier p
600+
| `CanonicalModuleType (_, `Resolved p) -> parent_module_type_identifier p
601+
| `CanonicalModuleType (p, _) -> parent_module_type_identifier p
602602
| `OpaqueModuleType mt -> parent_module_type_identifier mt
603603

604604
and parent_module_identifier :
@@ -669,8 +669,8 @@ module Path = struct
669669
| `Identifier id -> id
670670
| `ModuleType (m, n) -> `ModuleType (parent_module_identifier m, n)
671671
| `SubstT (s, _) -> identifier s
672-
| `CanonicalT (_, `Resolved p) -> identifier p
673-
| `CanonicalT (p, _) -> identifier p
672+
| `CanonicalModuleType (_, `Resolved p) -> identifier p
673+
| `CanonicalModuleType (p, _) -> identifier p
674674
| `OpaqueModuleType mt -> identifier mt
675675

676676
let rec canonical_ident : t -> Identifier.ModuleType.t option = function
@@ -680,8 +680,8 @@ module Path = struct
680680
| Some x -> Some (`ModuleType ((x :> Identifier.Signature.t), n))
681681
| None -> None )
682682
| `SubstT (_, _) -> None
683-
| `CanonicalT (_, `Resolved p) -> Some (identifier p)
684-
| `CanonicalT (_, _) -> None
683+
| `CanonicalModuleType (_, `Resolved p) -> Some (identifier p)
684+
| `CanonicalModuleType (_, _) -> None
685685
| `OpaqueModuleType m -> canonical_ident (m :> t)
686686
end
687687

@@ -695,8 +695,8 @@ module Path = struct
695695

696696
let rec identifier : t -> Identifier.Path.Type.t = function
697697
| `Identifier id -> id
698-
| `CanonicalTy (_, `Resolved t) -> identifier t
699-
| `CanonicalTy (t, _) -> identifier t
698+
| `CanonicalType (_, `Resolved t) -> identifier t
699+
| `CanonicalType (t, _) -> identifier t
700700
| `Type (m, n) -> `Type (parent_module_identifier m, n)
701701
| `Class (m, n) -> `Class (parent_module_identifier m, n)
702702
| `ClassType (m, n) -> `ClassType (parent_module_identifier m, n)
@@ -709,8 +709,8 @@ module Path = struct
709709
in
710710
function
711711
| `Identifier _ -> None
712-
| `CanonicalTy (_, `Resolved t) -> Some (identifier t)
713-
| `CanonicalTy (_, _) -> None
712+
| `CanonicalType (_, `Resolved t) -> Some (identifier t)
713+
| `CanonicalType (_, _) -> None
714714
| `Type (m, n) -> parent m None (fun sg -> Some (`Type (sg, n)))
715715
| `Class (m, n) -> parent m None (fun sg -> Some (`Class (sg, n)))
716716
| `ClassType (m, n) ->
@@ -748,10 +748,10 @@ module Path = struct
748748
if is_path_hidden (`Resolved (sub :> t)) then identifier (orig :> t)
749749
else identifier (sub :> t)
750750
| `SubstT (p, _) -> identifier (p :> t)
751-
| `CanonicalT (_, `Resolved p) -> identifier (p :> t)
752-
| `CanonicalT (p, _) -> identifier (p :> t)
753-
| `CanonicalTy (_, `Resolved p) -> identifier (p :> t)
754-
| `CanonicalTy (p, _) -> identifier (p :> t)
751+
| `CanonicalModuleType (_, `Resolved p) -> identifier (p :> t)
752+
| `CanonicalModuleType (p, _) -> identifier (p :> t)
753+
| `CanonicalType (_, `Resolved p) -> identifier (p :> t)
754+
| `CanonicalType (p, _) -> identifier (p :> t)
755755
| `OpaqueModule m -> identifier (m :> t)
756756
| `OpaqueModuleType mt -> identifier (mt :> t)
757757
end

src/model/paths_types.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -213,14 +213,14 @@ and Resolved_path : sig
213213
and module_type =
214214
[ `Identifier of Identifier.path_module_type
215215
| `SubstT of module_type * module_type
216-
| `CanonicalT of module_type * Path.module_type
216+
| `CanonicalModuleType of module_type * Path.module_type
217217
| `ModuleType of module_ * ModuleTypeName.t
218218
| `OpaqueModuleType of module_type ]
219219
(** @canonical Odoc_model.Paths.Path.Resolved.ModuleType.t *)
220220

221221
type type_ =
222222
[ `Identifier of Identifier.path_type
223-
| `CanonicalTy of type_ * Path.type_
223+
| `CanonicalType of type_ * Path.type_
224224
| `Type of module_ * TypeName.t
225225
| `Class of module_ * ClassName.t
226226
| `ClassType of module_ * ClassTypeName.t ]
@@ -242,10 +242,10 @@ and Resolved_path : sig
242242
| `Alias of module_ * module_
243243
| `OpaqueModule of module_
244244
| `ModuleType of module_ * ModuleTypeName.t
245-
| `CanonicalT of module_type * Path.module_type
245+
| `CanonicalModuleType of module_type * Path.module_type
246246
| `SubstT of module_type * module_type
247247
| `OpaqueModuleType of module_type
248-
| `CanonicalTy of type_ * Path.type_
248+
| `CanonicalType of type_ * Path.type_
249249
| `Type of module_ * TypeName.t
250250
| `Class of module_ * ClassName.t
251251
| `ClassType of module_ * ClassTypeName.t

src/model_desc/paths_desc.ml

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -224,10 +224,16 @@ module General_paths = struct
224224
( "`SubstT",
225225
((x1 :> rp), (x2 :> rp)),
226226
Pair (resolved_path, resolved_path) )
227-
| `CanonicalT (x1, x2) ->
228-
C ("`CanonicalT", ((x1 :> rp), (x2 :> p)), Pair (resolved_path, path))
229-
| `CanonicalTy (x1, x2) ->
230-
C ("`CanonicalTy", ((x1 :> rp), (x2 :> p)), Pair (resolved_path, path))
227+
| `CanonicalModuleType (x1, x2) ->
228+
C
229+
( "`CanonicalModuleType",
230+
((x1 :> rp), (x2 :> p)),
231+
Pair (resolved_path, path) )
232+
| `CanonicalType (x1, x2) ->
233+
C
234+
( "`CanonicalType",
235+
((x1 :> rp), (x2 :> p)),
236+
Pair (resolved_path, path) )
231237
| `OpaqueModuleType x -> C ("`OpaqueModuleType", (x :> rp), resolved_path)
232238
| `Type (x1, x2) ->
233239
C ("`Type", ((x1 :> rp), x2), Pair (resolved_path, Names.typename))

src/xref2/component.ml

Lines changed: 8 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -912,7 +912,7 @@ module Fmt = struct
912912
| `SubstT (m1, m2) ->
913913
Format.fprintf ppf "substt(%a,%a)" resolved_module_type_path m1
914914
resolved_module_type_path m2
915-
| `CanonicalT (m1, m2) ->
915+
| `CanonicalModuleType (m1, m2) ->
916916
Format.fprintf ppf "canonicalt(%a,%a)" resolved_module_type_path m1
917917
module_type_path m2
918918
| `OpaqueModuleType m ->
@@ -941,7 +941,7 @@ module Fmt = struct
941941
(id :> Odoc_model.Paths.Identifier.t)
942942
| `Substituted x ->
943943
Format.fprintf ppf "substituted(%a)" resolved_type_path x
944-
| `CanonicalTy (t1, t2) ->
944+
| `CanonicalType (t1, t2) ->
945945
Format.fprintf ppf "canonicalty(%a,%a)" resolved_type_path t1 type_path
946946
t2
947947
| `Class (p, t) ->
@@ -1070,12 +1070,12 @@ module Fmt = struct
10701070
(t1 :> t)
10711071
model_resolved_path
10721072
(t2 :> t)
1073-
| `CanonicalT (t1, t2) ->
1073+
| `CanonicalModuleType (t1, t2) ->
10741074
Format.fprintf ppf "canonicalt(%a,%a)" model_resolved_path
10751075
(t1 :> t)
10761076
model_path
10771077
(t2 :> Odoc_model.Paths.Path.t)
1078-
| `CanonicalTy (t1, t2) ->
1078+
| `CanonicalType (t1, t2) ->
10791079
Format.fprintf ppf "canonicalty(%a,%a)" model_resolved_path
10801080
(t1 :> t)
10811081
model_path
@@ -1650,8 +1650,8 @@ module Of_Lang = struct
16501650
`SubstT
16511651
( resolved_module_type_path ident_map p1,
16521652
resolved_module_type_path ident_map p2 )
1653-
| `CanonicalT (p1, p2) ->
1654-
`CanonicalT
1653+
| `CanonicalModuleType (p1, p2) ->
1654+
`CanonicalModuleType
16551655
(resolved_module_type_path ident_map p1, module_type_path ident_map p2)
16561656
| `OpaqueModuleType m ->
16571657
`OpaqueModuleType (resolved_module_type_path ident_map m)
@@ -1661,8 +1661,8 @@ module Of_Lang = struct
16611661
fun ident_map p ->
16621662
match p with
16631663
| `Identifier i -> identifier Maps.Path.Type.find ident_map.path_types i
1664-
| `CanonicalTy (p1, p2) ->
1665-
`CanonicalTy (resolved_type_path ident_map p1, type_path ident_map p2)
1664+
| `CanonicalType (p1, p2) ->
1665+
`CanonicalType (resolved_type_path ident_map p1, type_path ident_map p2)
16661666
| `Type (p, name) -> `Type (`Module (resolved_module_path ident_map p), name)
16671667
| `Class (p, name) ->
16681668
`Class (`Module (resolved_module_path ident_map p), name)

src/xref2/cpath.ml

Lines changed: 15 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -24,14 +24,14 @@ module rec Resolved : sig
2424
| `Identifier of Identifier.ModuleType.t
2525
| `ModuleType of parent * ModuleTypeName.t
2626
| `SubstT of module_type * module_type
27-
| `CanonicalT of module_type * Cpath.module_type
27+
| `CanonicalModuleType of module_type * Cpath.module_type
2828
| `OpaqueModuleType of module_type ]
2929

3030
and type_ =
3131
[ `Local of Ident.path_type
3232
| `Identifier of Odoc_model.Paths.Identifier.Path.Type.t
3333
| `Substituted of type_
34-
| `CanonicalTy of type_ * Cpath.type_
34+
| `CanonicalType of type_ * Cpath.type_
3535
| `Type of parent * TypeName.t
3636
| `Class of parent * ClassName.t
3737
| `ClassType of parent * ClassTypeName.t ]
@@ -134,7 +134,7 @@ and resolved_module_type_hash : Resolved.module_type -> int = function
134134
| `SubstT (p1, p2) ->
135135
Hashtbl.hash
136136
(23, resolved_module_type_hash p1, resolved_module_type_hash p2)
137-
| `CanonicalT (p1, p2) ->
137+
| `CanonicalModuleType (p1, p2) ->
138138
Hashtbl.hash (24, resolved_module_type_hash p1, module_type_hash p2)
139139
| `OpaqueModuleType m -> Hashtbl.hash (25, resolved_module_type_hash m)
140140

@@ -195,8 +195,8 @@ and resolved_module_type_path_of_cpath :
195195
`SubstT
196196
( resolved_module_type_path_of_cpath p1,
197197
resolved_module_type_path_of_cpath p2 )
198-
| `CanonicalT (p1, p2) ->
199-
`CanonicalT
198+
| `CanonicalModuleType (p1, p2) ->
199+
`CanonicalModuleType
200200
(resolved_module_type_path_of_cpath p1, module_type_path_of_cpath p2)
201201
| `OpaqueModuleType m ->
202202
`OpaqueModuleType (resolved_module_type_path_of_cpath m)
@@ -206,8 +206,8 @@ and resolved_type_path_of_cpath : Resolved.type_ -> Path.Resolved.Type.t =
206206
| `Identifier (#Odoc_model.Paths.Identifier.Path.Type.t as x) -> `Identifier x
207207
| `Local _ as y -> raise (LocalPath (ErrType (`Resolved y)))
208208
| `Substituted y -> resolved_type_path_of_cpath y
209-
| `CanonicalTy (t1, t2) ->
210-
`CanonicalTy (resolved_type_path_of_cpath t1, type_path_of_cpath t2)
209+
| `CanonicalType (t1, t2) ->
210+
`CanonicalType (resolved_type_path_of_cpath t1, type_path_of_cpath t2)
211211
| `Type (p, m) -> `Type (resolved_module_path_of_cpath_parent p, m)
212212
| `Class (p, m) -> `Class (resolved_module_path_of_cpath_parent p, m)
213213
| `ClassType (p, m) -> `ClassType (resolved_module_path_of_cpath_parent p, m)
@@ -286,14 +286,14 @@ and is_resolved_module_type_substituted : Resolved.module_type -> bool =
286286
| `Identifier _ -> false
287287
| `ModuleType (a, _) -> is_resolved_parent_substituted a
288288
| `SubstT _ -> false
289-
| `CanonicalT (m, _) | `OpaqueModuleType m ->
289+
| `CanonicalModuleType (m, _) | `OpaqueModuleType m ->
290290
is_resolved_module_type_substituted m
291291

292292
and is_resolved_type_substituted : Resolved.type_ -> bool = function
293293
| `Local _ -> false
294294
| `Substituted _ -> true
295295
| `Identifier _ -> false
296-
| `CanonicalTy (t, _) -> is_resolved_type_substituted t
296+
| `CanonicalType (t, _) -> is_resolved_type_substituted t
297297
| `Type (a, _) | `Class (a, _) | `ClassType (a, _) ->
298298
is_resolved_parent_substituted a
299299

@@ -398,8 +398,8 @@ and is_resolved_module_type_hidden : Resolved.module_type -> bool = function
398398
| `ModuleType (p, _) -> is_resolved_parent_hidden ~weak_canonical_test:false p
399399
| `SubstT (p1, p2) ->
400400
is_resolved_module_type_hidden p1 || is_resolved_module_type_hidden p2
401-
| `CanonicalT (_, `Resolved _) -> false
402-
| `CanonicalT (p, _) -> is_resolved_module_type_hidden p
401+
| `CanonicalModuleType (_, `Resolved _) -> false
402+
| `CanonicalModuleType (p, _) -> is_resolved_module_type_hidden p
403403
| `OpaqueModuleType m -> is_resolved_module_type_substituted m
404404

405405
and is_type_hidden : type_ -> bool = function
@@ -422,8 +422,8 @@ and is_resolved_type_hidden : Resolved.type_ -> bool = function
422422
| `Identifier (`Class (_, _)) -> false
423423
| `Identifier (`CoreType _) -> false
424424
| `Substituted p -> is_resolved_type_hidden p
425-
| `CanonicalTy (_, `Resolved _) -> false
426-
| `CanonicalTy (p, _) -> is_resolved_type_hidden p
425+
| `CanonicalType (_, `Resolved _) -> false
426+
| `CanonicalType (p, _) -> is_resolved_type_hidden p
427427
| `Type (p, _) | `Class (p, _) | `ClassType (p, _) ->
428428
is_resolved_parent_hidden ~weak_canonical_test:false p
429429

@@ -509,7 +509,7 @@ and unresolve_resolved_module_type_path : Resolved.module_type -> module_type =
509509
| `ModuleType (p, n) ->
510510
`Dot (unresolve_resolved_parent_path p, ModuleTypeName.to_string n)
511511
| `SubstT (_, m) -> unresolve_resolved_module_type_path m
512-
| `CanonicalT (p, _) -> unresolve_resolved_module_type_path p
512+
| `CanonicalModuleType (p, _) -> unresolve_resolved_module_type_path p
513513
| `OpaqueModuleType m -> unresolve_resolved_module_type_path m
514514

515515
and unresolve_resolved_parent_path : Resolved.parent -> module_ = function
@@ -519,7 +519,7 @@ and unresolve_resolved_parent_path : Resolved.parent -> module_ = function
519519
and unresolve_resolved_type_path : Resolved.type_ -> type_ = function
520520
| (`Identifier _ | `Local _) as p -> `Resolved p
521521
| `Substituted x -> unresolve_resolved_type_path x
522-
| `CanonicalTy (t1, _) -> unresolve_resolved_type_path t1
522+
| `CanonicalType (t1, _) -> unresolve_resolved_type_path t1
523523
| `Type (p, n) -> `Dot (unresolve_resolved_parent_path p, TypeName.to_string n)
524524
| `Class (p, n) ->
525525
`Dot (unresolve_resolved_parent_path p, ClassName.to_string n)

src/xref2/lang_of.ml

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -161,8 +161,8 @@ module Path = struct
161161
| `Substituted s -> resolved_module_type map s
162162
| `SubstT (p1, p2) ->
163163
`SubstT (resolved_module_type map p1, resolved_module_type map p2)
164-
| `CanonicalT (p1, p2) ->
165-
`CanonicalT (resolved_module_type map p1, module_type map p2)
164+
| `CanonicalModuleType (p1, p2) ->
165+
`CanonicalModuleType (resolved_module_type map p1, module_type map p2)
166166
| `OpaqueModuleType m -> `OpaqueModuleType (resolved_module_type map m)
167167

168168
and resolved_type map (p : Cpath.Resolved.type_) :
@@ -171,7 +171,8 @@ module Path = struct
171171
| `Identifier (#Odoc_model.Paths.Identifier.Path.Type.t as y) ->
172172
`Identifier y
173173
| `Local id -> `Identifier (Component.PathTypeMap.find id map.path_type)
174-
| `CanonicalTy (t1, t2) -> `CanonicalTy (resolved_type map t1, type_ map t2)
174+
| `CanonicalType (t1, t2) ->
175+
`CanonicalType (resolved_type map t1, type_ map t2)
175176
| `Type (p, name) -> `Type (resolved_parent map p, name)
176177
| `Class (p, name) -> `Class (resolved_parent map p, name)
177178
| `ClassType (p, name) -> `ClassType (resolved_parent map p, name)

src/xref2/link.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -59,9 +59,9 @@ let rec should_reresolve : Paths.Path.Resolved.t -> bool =
5959
| `Hidden p -> should_reresolve (p :> t)
6060
| `Canonical (x, y) ->
6161
should_reresolve (x :> t) || should_resolve (y :> Paths.Path.t)
62-
| `CanonicalT (x, y) ->
62+
| `CanonicalModuleType (x, y) ->
6363
should_reresolve (x :> t) || should_resolve (y :> Paths.Path.t)
64-
| `CanonicalTy (x, y) ->
64+
| `CanonicalType (x, y) ->
6565
should_reresolve (x :> t) || should_resolve (y :> Paths.Path.t)
6666
| `Apply (x, y) ->
6767
should_reresolve (x :> t) || should_reresolve (y :> Paths.Path.Resolved.t)

0 commit comments

Comments
 (0)