Skip to content

Commit 104ae93

Browse files
committed
Simplify idents
Use 'type_' idents instead of 'class_' and 'class_type'. Use 'module_' instead of 'functor_parameter' and 'result'. This allows to remove some code.
1 parent 6910541 commit 104ae93

File tree

14 files changed

+194
-434
lines changed

14 files changed

+194
-434
lines changed

src/xref2/component.ml

Lines changed: 26 additions & 58 deletions
Original file line numberDiff line numberDiff line change
@@ -12,32 +12,14 @@ module TypeMap = Map.Make (struct
1212
let compare a b = Ident.compare (a :> Ident.any) (b :> Ident.any)
1313
end)
1414

15-
module PathModuleMap = Map.Make (struct
16-
type t = Ident.path_module
17-
18-
let compare a b = Ident.compare (a :> Ident.any) (b :> Ident.any)
19-
end)
20-
2115
module ModuleTypeMap = Map.Make (struct
2216
type t = Ident.module_type
2317

2418
let compare a b = Ident.compare (a :> Ident.any) (b :> Ident.any)
2519
end)
2620

27-
module PathTypeMap = Map.Make (struct
28-
type t = Ident.path_type
29-
30-
let compare a b = Ident.compare (a :> Ident.any) (b :> Ident.any)
31-
end)
32-
33-
module PathValueMap = Map.Make (struct
34-
type t = Ident.path_value
35-
36-
let compare a b = Ident.compare (a :> Ident.any) (b :> Ident.any)
37-
end)
38-
39-
module PathClassTypeMap = Map.Make (struct
40-
type t = Ident.path_class_type
21+
module ValueMap = Map.Make (struct
22+
type t = Ident.value
4123

4224
let compare a b = Ident.compare (a :> Ident.any) (b :> Ident.any)
4325
end)
@@ -182,7 +164,7 @@ end =
182164
Exception
183165

184166
and FunctorParameter : sig
185-
type parameter = { id : Ident.functor_parameter; expr : ModuleType.expr }
167+
type parameter = { id : Ident.module_; expr : ModuleType.expr }
186168

187169
type t = Named of parameter | Unit
188170
end =
@@ -320,8 +302,8 @@ and Signature : sig
320302
| Exception of Ident.exception_ * Exception.t
321303
| TypExt of Extension.t
322304
| Value of Ident.value * Value.t Delayed.t
323-
| Class of Ident.class_ * recursive * Class.t
324-
| ClassType of Ident.class_type * recursive * ClassType.t
305+
| Class of Ident.type_ * recursive * Class.t
306+
| ClassType of Ident.type_ * recursive * ClassType.t
325307
| Include of Include.t
326308
| Open of Open.t
327309
| Comment of CComment.docs_or_stop
@@ -440,28 +422,27 @@ and Substitution : sig
440422
type subst_module =
441423
[ `Prefixed of Cpath.module_ * Cpath.Resolved.module_
442424
| `Substituted
443-
| `Renamed of Ident.path_module ]
425+
| `Renamed of Ident.module_ ]
444426

445427
type subst_module_type =
446428
[ `Prefixed of Cpath.module_type * Cpath.Resolved.module_type
447429
| `Renamed of Ident.module_type ]
448430

449431
type subst_type =
450-
[ `Prefixed of Cpath.type_ * Cpath.Resolved.type_
451-
| `Renamed of Ident.path_type ]
432+
[ `Prefixed of Cpath.type_ * Cpath.Resolved.type_ | `Renamed of Ident.type_ ]
452433

453434
type subst_class_type =
454435
[ `Prefixed of Cpath.class_type * Cpath.Resolved.class_type
455-
| `Renamed of Ident.path_class_type ]
436+
| `Renamed of Ident.type_ ]
456437

457438
type t = {
458-
module_ : subst_module PathModuleMap.t;
439+
module_ : subst_module ModuleMap.t;
459440
module_type : subst_module_type ModuleTypeMap.t;
460-
type_ : subst_type PathTypeMap.t;
461-
class_type : subst_class_type PathClassTypeMap.t;
462-
type_replacement : (TypeExpr.t * TypeDecl.Equation.t) PathTypeMap.t;
441+
type_ : subst_type TypeMap.t;
442+
class_type : subst_class_type TypeMap.t;
443+
type_replacement : (TypeExpr.t * TypeDecl.Equation.t) TypeMap.t;
463444
module_type_replacement : ModuleType.expr ModuleTypeMap.t;
464-
path_invalidating_modules : Ident.path_module list;
445+
path_invalidating_modules : Ident.module_ list;
465446
unresolve_opaque_paths : bool;
466447
}
467448
end =
@@ -1815,14 +1796,12 @@ module Of_Lang = struct
18151796
type map = {
18161797
modules : Ident.module_ Paths.Identifier.Maps.Module.t;
18171798
module_types : Ident.module_type Paths.Identifier.Maps.ModuleType.t;
1818-
functor_parameters :
1819-
Ident.functor_parameter Paths.Identifier.Maps.FunctorParameter.t;
1799+
functor_parameters : Ident.module_ Paths.Identifier.Maps.FunctorParameter.t;
18201800
types : Ident.type_ Paths.Identifier.Maps.Type.t;
1821-
path_types : Ident.path_type Paths.Identifier.Maps.Path.Type.t;
1822-
path_class_types :
1823-
Ident.path_class_type Paths.Identifier.Maps.Path.ClassType.t;
1824-
classes : Ident.class_ Paths.Identifier.Maps.Class.t;
1825-
class_types : Ident.class_type Paths.Identifier.Maps.ClassType.t;
1801+
path_types : Ident.type_ Paths.Identifier.Maps.Path.Type.t;
1802+
path_class_types : Ident.type_ Paths.Identifier.Maps.Path.ClassType.t;
1803+
classes : Ident.type_ Paths.Identifier.Maps.Class.t;
1804+
class_types : Ident.type_ Paths.Identifier.Maps.ClassType.t;
18261805
}
18271806

18281807
let empty () =
@@ -1848,10 +1827,7 @@ module Of_Lang = struct
18481827
(fun (types, path_types) i ->
18491828
let id = Ident.Of_Identifier.type_ i in
18501829
( Maps.Type.add i id types,
1851-
Maps.Path.Type.add
1852-
(i :> Path.Type.t)
1853-
(id :> Ident.path_type)
1854-
path_types ))
1830+
Maps.Path.Type.add (i :> Path.Type.t) id path_types ))
18551831
(map.types, map.path_types)
18561832
ids.LocalIdents.types
18571833
in
@@ -1860,10 +1836,8 @@ module Of_Lang = struct
18601836
(fun (classes, path_class_types) i ->
18611837
let id = Ident.Of_Identifier.class_ i in
18621838
( Maps.Class.add i id classes,
1863-
Maps.Path.ClassType.add
1864-
(i :> Path.ClassType.t)
1865-
(id :> Ident.path_class_type)
1866-
path_class_types ))
1839+
Maps.Path.ClassType.add (i :> Path.ClassType.t) id path_class_types
1840+
))
18671841
(map.classes, map.path_class_types)
18681842
ids.LocalIdents.classes
18691843
in
@@ -1872,14 +1846,9 @@ module Of_Lang = struct
18721846
(fun (class_types, path_types, path_class_types) i ->
18731847
let id = Ident.Of_Identifier.class_type i in
18741848
( Maps.ClassType.add i id class_types,
1875-
Maps.Path.Type.add
1876-
(i :> Path.Type.t)
1877-
(id :> Ident.path_type)
1878-
path_types,
1879-
Maps.Path.ClassType.add
1880-
(i :> Path.ClassType.t)
1881-
(id :> Ident.path_class_type)
1882-
path_class_types ))
1849+
Maps.Path.Type.add (i :> Path.Type.t) id path_types,
1850+
Maps.Path.ClassType.add (i :> Path.ClassType.t) id path_class_types
1851+
))
18831852
(map.class_types, path_types_new, path_class_types_new)
18841853
ids.LocalIdents.class_types
18851854
in
@@ -1925,13 +1894,12 @@ module Of_Lang = struct
19251894
let find_any_module i ident_map =
19261895
match i with
19271896
| { Odoc_model.Paths.Identifier.iv = `Root _ | `Module _; _ } as id ->
1928-
(Maps.Module.find id ident_map.modules :> Ident.path_module)
1897+
Maps.Module.find id ident_map.modules
19291898
| {
19301899
Odoc_model.Paths.Identifier.iv = #Paths.Identifier.FunctorParameter.t_pv;
19311900
_;
19321901
} as id ->
1933-
(Maps.FunctorParameter.find id ident_map.functor_parameters
1934-
:> Ident.path_module)
1902+
Maps.FunctorParameter.find id ident_map.functor_parameters
19351903
| _ -> raise Not_found
19361904

19371905
let rec resolved_module_path :

src/xref2/component.mli

Lines changed: 13 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -4,16 +4,9 @@ module ModuleMap : Map.S with type key = Ident.module_
44

55
module TypeMap : Map.S with type key = Ident.type_
66

7-
module PathModuleMap : Map.S with type key = Ident.path_module
8-
(** Useful maps *)
9-
107
module ModuleTypeMap : Map.S with type key = Ident.module_type
118

12-
module PathTypeMap : Map.S with type key = Ident.path_type
13-
14-
module PathValueMap : Map.S with type key = Ident.path_value
15-
16-
module PathClassTypeMap : Map.S with type key = Ident.path_class_type
9+
module ValueMap : Map.S with type key = Ident.value
1710

1811
module IdentMap : Map.S with type key = Ident.any
1912

@@ -162,7 +155,7 @@ and Exception : sig
162155
end
163156

164157
and FunctorParameter : sig
165-
type parameter = { id : Ident.functor_parameter; expr : ModuleType.expr }
158+
type parameter = { id : Ident.module_; expr : ModuleType.expr }
166159

167160
type t = Named of parameter | Unit
168161
end
@@ -285,8 +278,8 @@ and Signature : sig
285278
| Exception of Ident.exception_ * Exception.t
286279
| TypExt of Extension.t
287280
| Value of Ident.value * Value.t Delayed.t
288-
| Class of Ident.class_ * recursive * Class.t
289-
| ClassType of Ident.class_type * recursive * ClassType.t
281+
| Class of Ident.type_ * recursive * Class.t
282+
| ClassType of Ident.type_ * recursive * ClassType.t
290283
| Include of Include.t
291284
| Open of Open.t
292285
| Comment of CComment.docs_or_stop
@@ -407,28 +400,27 @@ and Substitution : sig
407400
type subst_module =
408401
[ `Prefixed of Cpath.module_ * Cpath.Resolved.module_
409402
| `Substituted
410-
| `Renamed of Ident.path_module ]
403+
| `Renamed of Ident.module_ ]
411404

412405
type subst_module_type =
413406
[ `Prefixed of Cpath.module_type * Cpath.Resolved.module_type
414407
| `Renamed of Ident.module_type ]
415408

416409
type subst_type =
417-
[ `Prefixed of Cpath.type_ * Cpath.Resolved.type_
418-
| `Renamed of Ident.path_type ]
410+
[ `Prefixed of Cpath.type_ * Cpath.Resolved.type_ | `Renamed of Ident.type_ ]
419411

420412
type subst_class_type =
421413
[ `Prefixed of Cpath.class_type * Cpath.Resolved.class_type
422-
| `Renamed of Ident.path_class_type ]
414+
| `Renamed of Ident.type_ ]
423415

424416
type t = {
425-
module_ : subst_module PathModuleMap.t;
417+
module_ : subst_module ModuleMap.t;
426418
module_type : subst_module_type ModuleTypeMap.t;
427-
type_ : subst_type PathTypeMap.t;
428-
class_type : subst_class_type PathClassTypeMap.t;
429-
type_replacement : (TypeExpr.t * TypeDecl.Equation.t) PathTypeMap.t;
419+
type_ : subst_type TypeMap.t;
420+
class_type : subst_class_type TypeMap.t;
421+
type_replacement : (TypeExpr.t * TypeDecl.Equation.t) TypeMap.t;
430422
module_type_replacement : ModuleType.expr ModuleTypeMap.t;
431-
path_invalidating_modules : Ident.path_module list;
423+
path_invalidating_modules : Ident.module_ list;
432424
unresolve_opaque_paths : bool;
433425
}
434426
end
@@ -773,7 +765,7 @@ module Of_Lang : sig
773765

774766
val functor_parameter :
775767
map ->
776-
Ident.functor_parameter ->
768+
Ident.module_ ->
777769
Odoc_model.Lang.FunctorParameter.parameter ->
778770
FunctorParameter.parameter
779771

src/xref2/cpath.ml

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,7 @@ module rec Resolved : sig
66
[ `Module of module_ | `ModuleType of module_type | `FragmentRoot ]
77

88
and module_ =
9-
[ `Local of Ident.path_module
9+
[ `Local of Ident.module_
1010
| `Gpath of Path.Resolved.Module.t
1111
| `Substituted of module_
1212
| `Subst of module_type * module_
@@ -28,7 +28,7 @@ module rec Resolved : sig
2828
| `OpaqueModuleType of module_type ]
2929

3030
and type_ =
31-
[ `Local of Ident.path_type
31+
[ `Local of Ident.type_
3232
| `Gpath of Path.Resolved.Type.t
3333
| `Substituted of type_
3434
| `CanonicalType of type_ * Path.Type.t
@@ -40,7 +40,7 @@ module rec Resolved : sig
4040
[ `Value of parent * ValueName.t | `Gpath of Path.Resolved.Value.t ]
4141

4242
and class_type =
43-
[ `Local of Ident.path_class_type
43+
[ `Local of Ident.type_
4444
| `Substituted of class_type
4545
| `Gpath of Path.Resolved.ClassType.t
4646
| `Class of parent * TypeName.t
@@ -52,7 +52,7 @@ and Cpath : sig
5252
type module_ =
5353
[ `Resolved of Resolved.module_
5454
| `Substituted of module_
55-
| `Local of Ident.path_module * bool
55+
| `Local of Ident.module_ * bool
5656
| `Identifier of Identifier.Path.Module.t * bool
5757
| `Root of ModuleName.t
5858
| `Forward of string
@@ -71,7 +71,7 @@ and Cpath : sig
7171
and type_ =
7272
[ `Resolved of Resolved.type_
7373
| `Substituted of type_
74-
| `Local of Ident.path_type * bool
74+
| `Local of Ident.type_ * bool
7575
| `Identifier of Odoc_model.Paths.Identifier.Path.Type.t * bool
7676
| `DotT of module_ * TypeName.t
7777
| `Type of Resolved.parent * TypeName.t
@@ -87,7 +87,7 @@ and Cpath : sig
8787
and class_type =
8888
[ `Resolved of Resolved.class_type
8989
| `Substituted of class_type
90-
| `Local of Ident.path_class_type * bool
90+
| `Local of Ident.type_ * bool
9191
| `Identifier of Odoc_model.Paths.Identifier.Path.ClassType.t * bool
9292
| `DotT of module_ * TypeName.t
9393
| `Class of Resolved.parent * TypeName.t

src/xref2/env.ml

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -667,9 +667,7 @@ let add_functor_args' :
667667
| ModuleType.Functor (Named arg, res) ->
668668
( arg.Component.FunctorParameter.id,
669669
Paths.Identifier.Mk.parameter
670-
( parent,
671-
Ident.Name.typed_functor_parameter
672-
arg.Component.FunctorParameter.id ),
670+
(parent, Ident.Name.typed_module arg.Component.FunctorParameter.id),
673671
mk_functor_parameter arg.expr )
674672
:: find_args (Paths.Identifier.Mk.result parent) res
675673
| ModuleType.Functor (Unit, res) ->
@@ -682,7 +680,7 @@ let add_functor_args' :
682680
themselves *)
683681
let fold_fn (env, subst) (ident, identifier, m) =
684682
let ident, identifier =
685-
((ident, identifier) :> Ident.path_module * Identifier.Path.Module.t)
683+
((ident, identifier) :> Ident.module_ * Identifier.Path.Module.t)
686684
in
687685
let doc = m.Component.Module.doc in
688686
let m = Component.Delayed.put_val (Subst.module_ subst m) in

src/xref2/errors.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ module Tools_error = struct
3737

3838
and simple_module_lookup_error =
3939
[ `Local of
40-
Env.t * Ident.path_module
40+
Env.t * Ident.module_
4141
(* Internal error: Found local path during lookup *)
4242
| `Find_failure
4343
| (* Internal error: the module was not found in the parent signature *)
@@ -71,7 +71,7 @@ module Tools_error = struct
7171

7272
and simple_type_lookup_error =
7373
[ `LocalType of
74-
Env.t * Ident.path_type
74+
Env.t * Ident.type_
7575
(* Internal error: Found local path during lookup *)
7676
| `Class_replaced
7777
(* Class was replaced with a destructive substitution and we're not sure
@@ -86,7 +86,7 @@ module Tools_error = struct
8686

8787
and simple_value_lookup_error =
8888
[ `LocalValue of
89-
Env.t * Ident.path_value
89+
Env.t * Ident.value
9090
(* Internal error: Found local path during lookup *)
9191
| `Find_failure
9292
(* Internal error: the type was not found in the parent signature *)

src/xref2/expand_tools.ml

Lines changed: 2 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -11,9 +11,7 @@ let handle_expansion env id expansion =
1111
| Named arg ->
1212
let identifier =
1313
Paths.Identifier.Mk.parameter
14-
( parent,
15-
Ident.Name.typed_functor_parameter
16-
arg.Component.FunctorParameter.id )
14+
(parent, Ident.Name.typed_module arg.Component.FunctorParameter.id)
1715
in
1816
let m = Component.module_of_functor_argument arg in
1917
let env' =
@@ -22,7 +20,7 @@ let handle_expansion env id expansion =
2220
let rp = `Gpath (`Identifier identifier) in
2321
let p = `Resolved rp in
2422
let subst =
25-
Subst.add_module (arg.id :> Ident.path_module) p rp Subst.identity
23+
Subst.add_module (arg.id :> Ident.module_) p rp Subst.identity
2624
in
2725
(env', Subst.module_type_expr subst expr)
2826
in

0 commit comments

Comments
 (0)