@@ -134,36 +134,25 @@ let directory_targets_of_rule ~dir { Rule_conf.targets; loc = rule_loc; enabled_
134134 when_enabled ~dir ~enabled_if directory_targets
135135;;
136136
137- let jsoo_wasm_enabled
138- ~(jsoo_submodes :
139- dir:Path.Build.t
140- -> submodes:Js_of_ocaml.Submode.Set.t option
141- -> Js_of_ocaml.Submode.t list Memo.t )
142- ~dir
143- ~submodes
144- =
145- let + submodes = jsoo_submodes ~dir ~submodes in
146- List. mem ~equal: Js_of_ocaml.Submode. equal submodes Wasm
137+ let jsoo_wasm_enabled ~jsoo_enabled ~dir ~(buildable : Buildable.t ) =
138+ let * expander = Expander0. get ~dir in
139+ jsoo_enabled
140+ ~eval: (Expander0. eval_blang expander)
141+ ~dir
142+ ~in_context: (Js_of_ocaml.In_context. make ~dir buildable.js_of_ocaml)
143+ ~mode: Js_of_ocaml.Mode. Wasm
147144;;
148145
149146let directory_targets_of_executables
150- ~jsoo_submodes
147+ ~jsoo_enabled
151148 ~dir
152149 { Executables. names; modes; enabled_if; buildable; _ }
153150 =
154151 let * directory_targets =
155152 (* CR-someday rgrinberg: we don't necessarily need to evalute
156- [explicit_js_mode] or [wasm_enabled] here *)
157- let + wasm_enabled =
158- jsoo_wasm_enabled ~jsoo_submodes ~dir ~submodes: buildable.js_of_ocaml.submodes
159- and + explicit_js_mode =
160- Scope.DB. find_by_dir dir >> | Scope. project >> | Dune_project. explicit_js_mode
161- in
162- match
163- Executables.Link_mode. (
164- Map. mem modes js || ((not explicit_js_mode) && Map. mem modes byte))
165- && wasm_enabled
166- with
153+ [wasm_enabled] here *)
154+ let + wasm_enabled = jsoo_wasm_enabled ~jsoo_enabled ~dir ~buildable in
155+ match Executables.Link_mode. (Map. mem modes wasm) && wasm_enabled with
167156 | false -> Path.Build.Map. empty
168157 | true ->
169158 Nonempty_list. to_list names
@@ -175,15 +164,15 @@ let directory_targets_of_executables
175164;;
176165
177166let directory_targets_of_library
178- ~jsoo_submodes
167+ ~jsoo_enabled
179168 ~dir
180169 { Library. sub_systems; name; enabled_if; buildable; _ }
181170 =
182171 let * directory_targets =
183172 match Sub_system_name.Map. find sub_systems Inline_tests_info.Tests. name with
184173 | Some (Inline_tests_info.Tests. T { modes; loc; enabled_if; _ })
185- when Inline_tests_info.Mode_conf.Set. mem modes Javascript ->
186- jsoo_wasm_enabled ~jsoo_submodes ~dir ~submodes: buildable.js_of_ocaml.submodes
174+ when Inline_tests_info.Mode_conf.Set. mem modes ( Jsoo Wasm ) ->
175+ jsoo_wasm_enabled ~jsoo_enabled ~dir ~buildable
187176 >> | (function
188177 | false -> Path.Build.Map. empty
189178 | true ->
@@ -207,13 +196,13 @@ let directory_targets_of_library
207196 when_enabled ~dir ~enabled_if directory_targets
208197;;
209198
210- let extract_directory_targets ~jsoo_submodes ~dir stanzas =
199+ let extract_directory_targets ~jsoo_enabled ~dir stanzas =
211200 Memo. parallel_map stanzas ~f: (fun stanza ->
212201 match Stanza. repr stanza with
213202 | Rule_conf. T rule -> directory_targets_of_rule ~dir rule
214203 | Executables. T exes | Tests. T { exes; _ } ->
215- directory_targets_of_executables ~jsoo_submodes ~dir exes
216- | Library. T lib -> directory_targets_of_library ~jsoo_submodes ~dir lib
204+ directory_targets_of_executables ~jsoo_enabled ~dir exes
205+ | Library. T lib -> directory_targets_of_library ~jsoo_enabled ~dir lib
217206 | Coq_stanza.Theory. T m ->
218207 (* It's unfortunate that we need to pull in the coq rules here. But
219208 we don't have a generic mechanism for this yet. *)
@@ -360,15 +349,15 @@ end = struct
360349 ;;
361350end
362351
363- let directory_targets t ~jsoo_submodes ~dir =
352+ let directory_targets t ~jsoo_enabled ~dir =
364353 match t with
365354 | Lock_dir | Generated | Source_only _ | Is_component_of_a_group_but_not_the_root _ ->
366355 Memo. return Path.Build.Map. empty
367356 | Standalone (_ , dune_file ) ->
368- Dune_file. stanzas dune_file >> = extract_directory_targets ~jsoo_submodes ~dir
357+ Dune_file. stanzas dune_file >> = extract_directory_targets ~jsoo_enabled ~dir
369358 | Group_root { components; dune_file; _ } ->
370359 let f ~dir stanzas acc =
371- extract_directory_targets ~jsoo_submodes ~dir stanzas
360+ extract_directory_targets ~jsoo_enabled ~dir stanzas
372361 >> | Path.Build.Map. superpose acc
373362 in
374363 let * init =
0 commit comments