Skip to content

Commit 82c670e

Browse files
authored
refactor: link time code gen cleanups (#7559)
* tighten up the scopes of variables * make the code generation a little lazier by delaying it until the rules are executed Signed-off-by: Rudi Grinberg <[email protected]>
1 parent b5c814e commit 82c670e

File tree

1 file changed

+18
-20
lines changed

1 file changed

+18
-20
lines changed

src/dune_rules/link_time_code_gen.ml

Lines changed: 18 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -138,17 +138,11 @@ let build_info_code cctx ~libs ~api_version =
138138
| Installed_private | Installed -> Memo.return ("None", placeholders)
139139
| Public (_, p) -> version_of_package placeholders p
140140
| Private _ ->
141-
let p =
142-
Lib.info lib |> Lib_info.obj_dir |> Obj_dir.dir
143-
|> Path.drop_build_context_exn
144-
in
145-
placeholder placeholders p)
141+
Lib.info lib |> Lib_info.obj_dir |> Obj_dir.dir
142+
|> Path.drop_build_context_exn |> placeholder placeholders)
146143
in
147144
((Lib.name lib, v) :: libs, placeholders))
148145
in
149-
let libs = List.rev libs in
150-
let context = Compilation_context.context cctx in
151-
let ocaml_version = Ocaml.Version.of_ocaml_config context.ocaml_config in
152146
let buf = Buffer.create 1024 in
153147
(* Parse the replacement format described in [artifact_substitution.ml]. *)
154148
pr buf
@@ -167,6 +161,8 @@ let build_info_code cctx ~libs ~api_version =
167161
[@@inline never]
168162
|ocaml};
169163
let fmt_eval : _ format6 =
164+
let context = Compilation_context.context cctx in
165+
let ocaml_version = Ocaml.Version.of_ocaml_config context.ocaml_config in
170166
if Ocaml.Version.has_sys_opaque_identity ocaml_version then
171167
"let %s = eval (Sys.opaque_identity %S)"
172168
else "let %s = eval %S"
@@ -177,7 +173,7 @@ let build_info_code cctx ~libs ~api_version =
177173
if not (Path.Source.Map.is_empty placeholders) then pr buf "";
178174
pr buf "let version = %s" version;
179175
pr buf "";
180-
prlist buf "statically_linked_libraries" libs ~f:(fun (name, v) ->
176+
prlist buf "statically_linked_libraries" (List.rev libs) ~f:(fun (name, v) ->
181177
pr buf "%S, %s" (Lib_name.to_string name) v);
182178
Buffer.contents buf
183179

@@ -222,8 +218,10 @@ let handle_special_libs cctx =
222218
let ( let& ) m f = Resolve.Memo.bind m ~f in
223219
let& all_libs = Compilation_context.requires_link cctx in
224220
let obj_dir = Compilation_context.obj_dir cctx |> Obj_dir.of_local in
225-
let sctx = Compilation_context.super_context cctx in
226-
let ctx = Super_context.context sctx in
221+
let ctx =
222+
let sctx = Compilation_context.super_context cctx in
223+
Super_context.context sctx
224+
in
227225
let open Memo.O in
228226
let* builtins =
229227
let+ findlib =
@@ -247,7 +245,8 @@ let handle_special_libs cctx =
247245
~obj_name:None
248246
~code:
249247
(Action_builder.of_memo
250-
(build_info_code cctx ~libs:all_libs ~api_version))
248+
(let* () = Memo.return () in
249+
build_info_code cctx ~libs:all_libs ~api_version))
251250
~requires:(Resolve.Memo.return [ lib ])
252251
~precompiled_cmi:true
253252
in
@@ -276,10 +275,10 @@ let handle_special_libs cctx =
276275
in
277276
generate_and_compile_module ~obj_name cctx ~lib ~name
278277
~code:
279-
(Action_builder.return
280-
(findlib_init_code
281-
~preds:Findlib.findlib_predicates_set_by_dune
282-
~libs:all_libs))
278+
(Action_builder.delayed (fun () ->
279+
findlib_init_code
280+
~preds:Findlib.findlib_predicates_set_by_dune
281+
~libs:all_libs))
283282
~requires ~precompiled_cmi:false
284283
in
285284
process_libs libs
@@ -290,10 +289,9 @@ let handle_special_libs cctx =
290289
process_libs libs ~to_link_rev:(Lib lib :: to_link_rev) ~force_linkall
291290
| Dune_site { data_module; plugins } ->
292291
let code =
293-
if plugins then
294-
Action_builder.return
295-
(dune_site_plugins_code ~libs:all_libs ~builtins)
296-
else Action_builder.return (dune_site_code ())
292+
Action_builder.delayed @@ fun () ->
293+
if plugins then dune_site_plugins_code ~libs:all_libs ~builtins
294+
else dune_site_code ()
297295
in
298296
let& module_ =
299297
generate_and_compile_module cctx ~obj_name:None ~name:data_module

0 commit comments

Comments
 (0)