@@ -29,7 +29,7 @@ let default_context_flags (ctx : Build_context.t) ocaml_config ~project =
29
29
module Env_tree : sig
30
30
type t
31
31
32
- val force_bin_artifacts : t -> unit Memo .t
32
+ val force_artifacts : t -> unit Memo .t
33
33
val context : t -> Context .t
34
34
val get_node : t -> dir :Path .Build .t -> Env_node .t Memo .t
35
35
val get_context_env : t -> Env .t
@@ -39,11 +39,11 @@ module Env_tree : sig
39
39
-> host_env_tree:t option
40
40
-> default_env:Env_node. t Memo.Lazy. t
41
41
-> root_expander:Expander. t
42
- -> bin_artifacts :Artifacts. t
42
+ -> artifacts :Artifacts. t
43
43
-> context_env:Env. t
44
44
-> t
45
45
46
- val bin_artifacts_host : t -> dir :Path .Build .t -> Artifacts .t Memo .t
46
+ val artifacts_host : t -> dir :Path .Build .t -> Artifacts .t Memo .t
47
47
val expander : t -> dir :Path .Build .t -> Expander .t Memo .t
48
48
end = struct
49
49
open Memo.O
@@ -54,25 +54,25 @@ end = struct
54
54
; default_env : Env_node .t Memo.Lazy .t
55
55
; host : t option
56
56
; root_expander : Expander .t
57
- ; bin_artifacts : Artifacts .t
57
+ ; artifacts : Artifacts .t
58
58
; get_node : Path.Build .t -> Env_node .t Memo .t
59
59
}
60
60
61
- let force_bin_artifacts { bin_artifacts ; _ } = Artifacts. force bin_artifacts
61
+ let force_artifacts { artifacts ; _ } = Artifacts. force artifacts
62
62
let context t = t.context
63
63
let get_node t ~dir = t.get_node dir
64
64
let get_context_env t = t.context_env
65
65
66
- let bin_artifacts_host t ~dir =
67
- let bin_artifacts t ~dir = get_node t ~dir >> = Env_node. bin_artifacts in
66
+ let artifacts_host t ~dir =
67
+ let artifacts t ~dir = get_node t ~dir >> = Env_node. artifacts in
68
68
match t.host with
69
- | None -> bin_artifacts t ~dir
69
+ | None -> artifacts t ~dir
70
70
| Some host ->
71
71
let dir =
72
72
Path.Build. drop_build_context_exn dir
73
73
|> Path.Build. append_source (Context. build_dir host.context)
74
74
in
75
- bin_artifacts host ~dir
75
+ artifacts host ~dir
76
76
;;
77
77
78
78
let external_env t ~dir = get_node t ~dir >> = Env_node. external_env
@@ -97,14 +97,14 @@ end = struct
97
97
;;
98
98
99
99
let extend_expander t ~dir ~expander_for_artifacts =
100
- let + bin_artifacts_host = bin_artifacts_host t ~dir
100
+ let + artifacts_host = artifacts_host t ~dir
101
101
and + bindings =
102
102
let + inline_tests = get_node t ~dir >> = Env_node. inline_tests in
103
103
let str = Dune_env.Stanza.Inline_tests. to_string inline_tests in
104
104
Pform.Map. singleton (Var Inline_tests ) [ Value. String str ]
105
105
in
106
106
Expander. add_bindings ~bindings expander_for_artifacts
107
- |> Expander. set_bin_artifacts ~bin_artifacts_host
107
+ |> Expander. set_artifacts ~artifacts_host
108
108
;;
109
109
110
110
let expander t ~dir =
@@ -177,7 +177,7 @@ end = struct
177
177
~expander_for_artifacts
178
178
~default_context_flags
179
179
~default_env: t.context_env
180
- ~default_bin_artifacts : t.bin_artifacts
180
+ ~default_artifacts : t.artifacts
181
181
~default_bin_annot: true
182
182
;;
183
183
@@ -192,14 +192,7 @@ end = struct
192
192
binding. To work around this limitation, we place the functions into a
193
193
recursive module [Rec]. Since recursive let-modules are not allowed either,
194
194
we need to also wrap [Rec] inside a non-recursive module [Non_rec]. *)
195
- let create
196
- ~context
197
- ~host_env_tree
198
- ~default_env
199
- ~root_expander
200
- ~bin_artifacts
201
- ~context_env
202
- =
195
+ let create ~context ~host_env_tree ~default_env ~root_expander ~artifacts ~context_env =
203
196
let module Non_rec = struct
204
197
module rec Rec : sig
205
198
val env_tree : unit -> t
@@ -211,7 +204,7 @@ end = struct
211
204
; default_env
212
205
; host = host_env_tree
213
206
; root_expander
214
- ; bin_artifacts
207
+ ; artifacts
215
208
; get_node = Rec. memo
216
209
}
217
210
;;
@@ -330,8 +323,8 @@ let dump_env t ~dir =
330
323
;;
331
324
332
325
let resolve_program t ~dir ?hint ~loc bin =
333
- let * bin_artifacts = Env_tree. bin_artifacts_host t ~dir in
334
- Artifacts. binary ?hint ~loc bin_artifacts bin
326
+ let * artifacts = Env_tree. artifacts_host t ~dir in
327
+ Artifacts. binary ?hint ~loc artifacts bin
335
328
;;
336
329
337
330
let add_packages_env context ~base stanzas packages =
@@ -437,7 +430,7 @@ let make_default_env_node
437
430
~expander_for_artifacts
438
431
~default_context_flags
439
432
~default_env: root_env
440
- ~default_bin_artifacts : artifacts
433
+ ~default_artifacts : artifacts
441
434
~default_bin_annot: true
442
435
in
443
436
make
@@ -510,7 +503,7 @@ let create ~(context : Context.t) ~(host : t option) ~packages ~stanzas =
510
503
~context
511
504
~env: expander_env
512
505
~lib_artifacts: public_libs
513
- ~bin_artifacts_host: artifacts_host
506
+ ~artifacts_host
514
507
~lib_artifacts_host: public_libs_host
515
508
and + artifacts = artifacts
516
509
and + root_env =
@@ -535,7 +528,7 @@ let create ~(context : Context.t) ~(host : t option) ~packages ~stanzas =
535
528
~default_env
536
529
~host_env_tree: host
537
530
~root_expander
538
- ~bin_artifacts: artifacts
531
+ ~artifacts
539
532
~context_env: root_env
540
533
;;
541
534
@@ -580,7 +573,7 @@ let find name =
580
573
581
574
let all_init_deferred () =
582
575
let * all = Memo.Lazy. force all in
583
- Context_name.Map. values all |> Memo. parallel_iter ~f: Env_tree. force_bin_artifacts
576
+ Context_name.Map. values all |> Memo. parallel_iter ~f: Env_tree. force_artifacts
584
577
;;
585
578
586
579
module As_memo_key = struct
0 commit comments