Skip to content

Commit 7838199

Browse files
authored
refactor: move standard aliases to rules (#11030)
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 09b7a19 commit 7838199

File tree

7 files changed

+16
-23
lines changed

7 files changed

+16
-23
lines changed

bin/alias.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
open Import
22
module Alias = Dune_engine.Alias
3+
module Alias0 = Dune_rules.Alias
34
module Alias_builder = Dune_rules.Alias_builder
45

56
type t =
@@ -96,7 +97,7 @@ let dep_on_alias_rec_multi_contexts ~dir:src_dir ~name ~contexts =
9697
Dune_rules.Alias_rec.dep_on_alias_rec name dir))
9798
in
9899
match
99-
Alias.is_standard name
100+
Alias0.is_standard name
100101
|| List.exists alias_statuses ~f:(fun (x : Alias_builder.Alias_status.t) ->
101102
match x with
102103
| Defined -> true

src/dune_engine/alias.ml

Lines changed: 0 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -78,22 +78,6 @@ let name t = t.name
7878
let dir t = t.dir
7979
let fully_qualified_name t = Path.Build.relative t.dir (Name.to_string t.name)
8080

81-
(* This mutable table is safe: it's modified only at the top level. *)
82-
let standard_aliases = Table.create (module Name) 7
83-
let is_standard name = Table.mem standard_aliases name
84-
85-
let make_standard name =
86-
Table.add_exn standard_aliases name ();
87-
make name
88-
;;
89-
90-
let register_as_standard name =
91-
let (_ : (unit, _) result) = Table.add standard_aliases name () in
92-
()
93-
;;
94-
95-
let default = make_standard Name.default
96-
9781
let get_ctx (path : Path.Build.t) =
9882
match Path.Build.extract_first_component path with
9983
| None -> None

src/dune_engine/alias.mli

Lines changed: 0 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,6 @@ val equal : t -> t -> bool
1515
val hash : t -> int
1616
val compare : t -> t -> Ordering.t
1717
val make : Name.t -> dir:Path.Build.t -> t
18-
val register_as_standard : Name.t -> unit
1918

2019
(** The following always holds: [make (name t) ~dir:(dir t) = t] *)
2120
val name : t -> Name.t
@@ -24,6 +23,4 @@ val dir : t -> Path.Build.t
2423
val to_dyn : t -> Dyn.t
2524
val of_user_written_path : loc:Loc.t -> Path.t -> t
2625
val fully_qualified_name : t -> Path.Build.t
27-
val default : dir:Path.Build.t -> t
28-
val is_standard : Name.t -> bool
2926
val describe : ?loc:Loc.t -> t -> _ Pp.t

src/dune_rules/alias0.ml

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,8 +1,17 @@
11
open Import
22

3+
(* This mutable table is safe: it's modified only at the top level. *)
4+
let standard_aliases = Table.create (module Dune_engine.Alias.Name) 7
5+
let is_standard name = Table.mem standard_aliases name
6+
7+
let register_as_standard name =
8+
let (_ : (unit, _) result) = Table.add standard_aliases name () in
9+
()
10+
;;
11+
312
let standard name =
413
let name = Alias.Name.of_string name in
5-
Alias.register_as_standard name;
14+
register_as_standard name;
615
name
716
;;
817

src/dune_rules/alias0.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -15,3 +15,5 @@ val ocaml_index : Name.t
1515
val install : Name.t
1616
val runtest : Name.t
1717
val all : Name.t
18+
val is_standard : Name.t -> bool
19+
val register_as_standard : Name.t -> unit

src/dune_rules/dep_conf_eval.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,7 @@ let dep_on_alias_rec alias ~loc =
6363
>>| (function
6464
| Defined -> ()
6565
| Not_defined ->
66-
if not (Alias.is_standard name)
66+
if not (Alias0.is_standard name)
6767
then
6868
User_error.raise
6969
~loc

src/dune_rules/jsoo/js_of_ocaml.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -214,7 +214,7 @@ module Env = struct
214214
(Dune_lang.Syntax.since Stanza.syntax (3, 17) >>> Sourcemap.decode)
215215
and+ runtest_alias = field_o "runtest_alias" Dune_lang.Alias.decode
216216
and+ flags = Flags.decode in
217-
Option.iter ~f:Alias.register_as_standard runtest_alias;
217+
Option.iter ~f:Alias0.register_as_standard runtest_alias;
218218
{ compilation_mode; sourcemap; runtest_alias; flags }
219219
;;
220220

0 commit comments

Comments
 (0)