Skip to content

Commit f7af2d0

Browse files
authored
refactor: remove [Lib_config] from [Lib] (#11105)
Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 619c098 commit f7af2d0

File tree

14 files changed

+125
-62
lines changed

14 files changed

+125
-62
lines changed

bin/ocaml/top.ml

Lines changed: 18 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -19,8 +19,12 @@ let info = Cmd.info "top" ~doc ~man
1919

2020
let link_deps sctx link =
2121
let open Memo.O in
22+
let* lib_config =
23+
let+ ocaml = Super_context.context sctx |> Context.ocaml in
24+
ocaml.lib_config
25+
in
2226
Memo.parallel_map link ~f:(fun t ->
23-
Dune_rules.Lib_flags.link_deps sctx t Dune_rules.Link_mode.Byte)
27+
Dune_rules.Lib_flags.link_deps sctx t Dune_rules.Link_mode.Byte lib_config)
2428
>>| List.concat
2529
;;
2630

@@ -47,9 +51,10 @@ let term =
4751
let sctx =
4852
Dune_engine.Context_name.Map.find setup.scontexts ctx_name |> Option.value_exn
4953
in
54+
let context = Super_context.context sctx in
5055
let* libs =
5156
let dir =
52-
let build_dir = Super_context.context sctx |> Context.build_dir in
57+
let build_dir = Context.build_dir context in
5358
Path.Build.relative build_dir (Common.prefix_target common dir)
5459
in
5560
let* db =
@@ -62,7 +67,13 @@ let term =
6267
let* requires =
6368
Dune_rules.Resolve.Memo.read_memo (Dune_rules.Lib.closure ~linking:true libs)
6469
in
65-
let include_paths = Dune_rules.Lib_flags.L.toplevel_include_paths requires in
70+
let* lib_config =
71+
let+ ocaml = Context.ocaml context in
72+
ocaml.lib_config
73+
in
74+
let include_paths =
75+
Dune_rules.Lib_flags.L.toplevel_include_paths requires lib_config
76+
in
6677
let+ files_to_load = files_to_load_of_requires sctx requires in
6778
Dune_rules.Toplevel.print_toplevel_init_file
6879
{ include_paths; files_to_load; uses = []; pp = None; ppx = None; code = [] }))
@@ -116,7 +127,10 @@ module Module = struct
116127
in
117128
let private_obj_dir = Top_module.private_obj_dir ctx mod_ in
118129
let include_paths =
119-
let libs = Dune_rules.Lib_flags.L.toplevel_include_paths requires in
130+
let libs =
131+
let lib_config = (Compilation_context.ocaml cctx).lib_config in
132+
Dune_rules.Lib_flags.L.toplevel_include_paths requires lib_config
133+
in
120134
Path.Set.add libs (Path.build (Obj_dir.byte_dir private_obj_dir))
121135
in
122136
let files_to_load () =

bin/ocaml/utop.ml

Lines changed: 6 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ let term =
2121
let dir = Common.prefix_target common dir in
2222
if not (Path.is_directory (Path.of_string dir))
2323
then User_error.raise [ Pp.textf "cannot find directory: %s" (String.maybe_quoted dir) ];
24-
let env, utop_path, requires =
24+
let env, lib_config, utop_path, requires =
2525
Scheduler.go ~common ~config (fun () ->
2626
let open Fiber.O in
2727
let* setup = Import.Main.setup () in
@@ -46,12 +46,15 @@ let term =
4646
Utop.requires_under_dir sctx ~dir
4747
in
4848
let+ requires = Resolve.read_memo requires
49+
and+ lib_config =
50+
let+ ocaml = Context.ocaml context in
51+
ocaml.lib_config
4952
and+ env = Super_context.context_env sctx in
50-
env, Path.to_string utop_target, requires))
53+
env, lib_config, Path.to_string utop_target, requires))
5154
in
5255
Hooks.End_of_build.run ();
5356
let env =
54-
Dune_rules.Lib_flags.L.toplevel_ld_paths requires
57+
Dune_rules.Lib_flags.L.toplevel_ld_paths requires lib_config
5558
|> Path.Set.fold
5659
~f:(fun dir env -> Env_path.cons ~var:Ocaml.Env.caml_ld_library_path env ~dir)
5760
~init:env

src/dune_rules/compilation_context.ml

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,11 +4,13 @@ open Memo.O
44
module Includes = struct
55
type t = Command.Args.without_targets Command.Args.t Lib_mode.Cm_kind.Map.t
66

7-
let make ~project ~opaque ~direct_requires ~hidden_requires : _ Lib_mode.Cm_kind.Map.t =
7+
let make ~project ~opaque ~direct_requires ~hidden_requires lib_config
8+
: _ Lib_mode.Cm_kind.Map.t
9+
=
810
(* TODO : some of the requires can filtered out using [ocamldep] info *)
911
let open Resolve.Memo.O in
1012
let iflags direct_libs hidden_libs mode =
11-
Lib_flags.L.include_flags ~project ~direct_libs ~hidden_libs mode
13+
Lib_flags.L.include_flags ~project ~direct_libs ~hidden_libs mode lib_config
1214
in
1315
let make_includes_args ~mode groups =
1416
Command.Args.memo
@@ -203,7 +205,8 @@ let create
203205
; requires_compile = direct_requires
204206
; requires_hidden = hidden_requires
205207
; requires_link
206-
; includes = Includes.make ~project ~opaque ~direct_requires ~hidden_requires
208+
; includes =
209+
Includes.make ~project ~opaque ~direct_requires ~hidden_requires ocaml.lib_config
207210
; preprocessing
208211
; opaque
209212
; stdlib
@@ -293,6 +296,7 @@ let for_module_generated_at_link_time cctx ~requires ~module_ =
293296
~opaque
294297
~direct_requires
295298
~hidden_requires
299+
cctx.ocaml.lib_config
296300
in
297301
{ cctx with
298302
opaque

src/dune_rules/ctypes/ctypes_rules.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -225,7 +225,8 @@ let build_c_program
225225
Lib.DB.resolve (Scope.libs scope) (Loc.none, ctypes) |> Resolve.Memo.read
226226
in
227227
let ctypes_include_dirs =
228-
Lib_flags.L.include_paths [ lib ] (Ocaml Native) |> Path.Set.to_list
228+
Lib_flags.L.include_paths [ lib ] (Ocaml Native) ocaml.lib_config
229+
|> Path.Set.to_list
229230
in
230231
let include_dirs = ocaml_where :: ctypes_include_dirs in
231232
Command.Args.S

src/dune_rules/jsoo/jsoo_rules.ml

Lines changed: 7 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -521,18 +521,22 @@ let setup_separate_compilation_rules sctx components =
521521
| Some pkg ->
522522
let info = Lib.info pkg in
523523
let lib_name = Lib_name.to_string (Lib.name pkg) in
524-
let archives =
524+
let* archives =
525525
let archives = (Lib_info.archives info).byte in
526526
(* Special case for the stdlib because it is not referenced in the
527527
META *)
528528
match lib_name with
529529
| "stdlib" ->
530+
let+ lib_config =
531+
let+ ocaml = Context.ocaml ctx in
532+
ocaml.lib_config
533+
in
530534
let archive =
531-
let stdlib_dir = (Lib.lib_config pkg).stdlib_dir in
535+
let stdlib_dir = lib_config.stdlib_dir in
532536
Path.relative stdlib_dir
533537
in
534538
archive "stdlib.cma" :: archive "std_exit.cmo" :: archives
535-
| _ -> archives
539+
| _ -> Memo.return archives
536540
in
537541
Memo.parallel_iter Js_of_ocaml.Mode.all ~f:(fun mode ->
538542
Memo.parallel_iter archives ~f:(fun fn ->

src/dune_rules/lib.ml

Lines changed: 2 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -337,7 +337,6 @@ module T = struct
337337
; pps : t list Resolve.t
338338
; resolved_selects : Resolved_select.t list Resolve.t
339339
; implements : t Resolve.t option
340-
; lib_config : Lib_config.t
341340
; project : Dune_project.t option
342341
; (* these fields cannot be forced until the library is instantiated *)
343342
default_implementation : t Resolve.t Memo.Lazy.t option
@@ -413,7 +412,6 @@ type db =
413412
; instantiate :
414413
(Lib_name.t -> Path.t Lib_info.t -> hidden:string option -> Status.t Memo.t) Lazy.t
415414
; all : Lib_name.t list Memo.Lazy.t
416-
; lib_config : Lib_config.t
417415
; instrument_with : Lib_name.t list
418416
}
419417

@@ -427,7 +425,6 @@ and resolve_result =
427425
| Redirect_by_name of db * (Loc.t * Lib_name.t)
428426
| Redirect_by_id of db * Lib_id.t
429427

430-
let lib_config (t : lib) = t.lib_config
431428
let name t = t.name
432429
let info t = t.info
433430
let project t = t.project
@@ -1070,7 +1067,6 @@ end = struct
10701067
; re_exports
10711068
; implements
10721069
; default_implementation
1073-
; lib_config = db.lib_config
10741070
; project
10751071
; sub_systems =
10761072
Sub_system_name.Map.mapi (Lib_info.sub_systems info) ~f:(fun name info ->
@@ -1909,14 +1905,13 @@ module DB = struct
19091905

19101906
type t = db
19111907

1912-
let create ~parent ~resolve ~resolve_lib_id ~all ~lib_config ~instrument_with () =
1908+
let create ~parent ~resolve ~resolve_lib_id ~all ~instrument_with () =
19131909
let rec t =
19141910
lazy
19151911
{ parent
19161912
; resolve
19171913
; resolve_lib_id
19181914
; all = Memo.lazy_ all
1919-
; lib_config
19201915
; instrument_with
19211916
; instantiate
19221917
}
@@ -1926,7 +1921,7 @@ module DB = struct
19261921

19271922
let create_from_findlib =
19281923
let bigarray = Lib_name.of_string "bigarray" in
1929-
fun findlib ~has_bigarray_library ~lib_config ->
1924+
fun findlib ~has_bigarray_library ->
19301925
let resolve name =
19311926
let open Memo.O in
19321927
Findlib.find findlib name
@@ -1951,7 +1946,6 @@ module DB = struct
19511946
create
19521947
()
19531948
~parent:None
1954-
~lib_config
19551949
~resolve
19561950
~resolve_lib_id:(fun lib_id ->
19571951
let open Memo.O in
@@ -1969,7 +1963,6 @@ module DB = struct
19691963
findlib
19701964
~has_bigarray_library:(Ocaml.Version.has_bigarray_library ocaml.version)
19711965
~instrument_with:(Context.instrument_with context)
1972-
~lib_config:ocaml.lib_config
19731966
;;
19741967

19751968
let find t name =

src/dune_rules/lib.mli

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,6 @@ val to_dyn : t -> Dyn.t
1111
or the [name] if not. *)
1212
val name : t -> Lib_name.t
1313

14-
val lib_config : t -> Lib_config.t
1514
val implements : t -> t Resolve.Memo.t option
1615

1716
(** [is_local t] returns [true] whenever [t] is defined in the local workspace *)
@@ -116,7 +115,6 @@ module DB : sig
116115
-> resolve:(Lib_name.t -> Resolve_result.t list Memo.t)
117116
-> resolve_lib_id:(Lib_id.t -> Resolve_result.t Memo.t)
118117
-> all:(unit -> Lib_name.t list Memo.t)
119-
-> lib_config:Lib_config.t
120118
-> instrument_with:Lib_name.t list
121119
-> unit
122120
-> t

src/dune_rules/lib_flags.ml

Lines changed: 35 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -12,7 +12,7 @@ module Link_params = struct
1212
not appear on the command line *)
1313
}
1414

15-
let get sctx (t : Lib.t) (mode : Link_mode.t) =
15+
let get sctx (t : Lib.t) (mode : Link_mode.t) (lib_config : Lib_config.t) =
1616
let info = Lib.info t in
1717
let lib_files = Lib_info.foreign_archives info
1818
and dll_files = Lib_info.foreign_dll_files info in
@@ -69,15 +69,15 @@ module Link_params = struct
6969
Path.extend_basename obj_name ~suffix:(Cm_kind.ext Cmo) :: hidden_deps
7070
| Native ->
7171
Path.extend_basename obj_name ~suffix:(Cm_kind.ext Cmx)
72-
:: Path.extend_basename obj_name ~suffix:(Lib.lib_config t).ext_obj
72+
:: Path.extend_basename obj_name ~suffix:lib_config.ext_obj
7373
:: hidden_deps)
7474
in
7575
{ deps; hidden_deps; include_dirs }
7676
;;
7777
end
7878

79-
let link_deps sctx t mode =
80-
let+ x = Link_params.get sctx t mode in
79+
let link_deps sctx t mode lib_config =
80+
let+ x = Link_params.get sctx t mode lib_config in
8181
List.rev_append x.hidden_deps x.deps
8282
;;
8383

@@ -94,10 +94,8 @@ module L = struct
9494
let to_iflags dir = to_flags "-I" dir
9595
let to_hflags dir = to_flags "-H" dir
9696

97-
let remove_stdlib dirs libs =
98-
match libs with
99-
| [] -> dirs
100-
| lib :: _ -> Path.Set.remove dirs (Lib.lib_config lib).stdlib_dir
97+
let remove_stdlib dirs (lib_config : Lib_config.t) =
98+
Path.Set.remove dirs lib_config.stdlib_dir
10199
;;
102100

103101
type mode =
@@ -125,7 +123,7 @@ module L = struct
125123
in
126124
List.fold_left public_cmi_dirs ~init:acc ~f:Path.Set.add
127125
in
128-
fun ?project ts mode ->
126+
fun ?project ts mode lib_config ->
129127
let visible_cmi =
130128
match project with
131129
| None -> fun _ -> true
@@ -154,33 +152,35 @@ module L = struct
154152
let native_dir = Obj_dir.native_dir obj_dir in
155153
Path.Set.add acc native_dir))
156154
in
157-
remove_stdlib dirs ts
155+
remove_stdlib dirs lib_config
158156
;;
159157

160-
let include_flags ?project ~direct_libs ~hidden_libs mode =
158+
let include_flags ?project ~direct_libs ~hidden_libs mode lib_config =
161159
let include_paths ts =
162160
include_paths ?project ts { lib_mode = mode; melange_emit = false }
163161
in
164-
let hidden_includes = to_hflags (include_paths hidden_libs) in
165-
let direct_includes = to_iflags (include_paths direct_libs) in
162+
let hidden_includes = to_hflags (include_paths hidden_libs lib_config) in
163+
let direct_includes = to_iflags (include_paths direct_libs lib_config) in
166164
Command.Args.S [ direct_includes; hidden_includes ]
167165
;;
168166

169-
let melange_emission_include_flags ?project ts =
170-
to_iflags (include_paths ?project ts { lib_mode = Melange; melange_emit = true })
167+
let melange_emission_include_flags ?project ts lib_config =
168+
to_iflags
169+
(include_paths ?project ts { lib_mode = Melange; melange_emit = true } lib_config)
171170
;;
172171

173172
let include_paths ?project ts mode =
174173
include_paths ?project ts { lib_mode = mode; melange_emit = false }
175174
;;
176175

177-
let c_include_paths ts =
176+
let c_include_paths ts lib_config =
178177
let dirs =
179178
List.fold_left ts ~init:Path.Set.empty ~f:(fun acc t ->
180179
let src_dir = Lib_info.src_dir (Lib.info t) in
181180
Path.Set.add acc src_dir)
182181
in
183-
remove_stdlib dirs ts
182+
(* I don't remember why this is being done anymore. Anyone else has a clue? *)
183+
remove_stdlib dirs lib_config
184184
;;
185185

186186
let c_include_flags ts sctx =
@@ -205,7 +205,17 @@ module L = struct
205205
let+ () = Action_builder.all_unit bindings in
206206
Command.Args.empty
207207
in
208-
Command.Args.S [ Dyn local; Hidden_deps external_; to_iflags (c_include_paths ts) ]
208+
let include_flags =
209+
let open Action_builder.O in
210+
let+ lib_config =
211+
Action_builder.of_memo
212+
Memo.O.(
213+
let+ ocaml = Super_context.context sctx |> Context.ocaml in
214+
ocaml.lib_config)
215+
in
216+
to_iflags (c_include_paths ts lib_config)
217+
in
218+
Command.Args.S [ Dyn local; Hidden_deps external_; Dyn include_flags ]
209219
;;
210220

211221
let toplevel_ld_paths ts =
@@ -218,8 +228,10 @@ module L = struct
218228
c_include_paths with_dlls
219229
;;
220230

221-
let toplevel_include_paths ts =
222-
Path.Set.union (include_paths ts (Lib_mode.Ocaml Byte)) (toplevel_ld_paths ts)
231+
let toplevel_include_paths ts lib_config =
232+
Path.Set.union
233+
(include_paths ts (Lib_mode.Ocaml Byte) lib_config)
234+
(toplevel_ld_paths ts lib_config)
223235
;;
224236
end
225237

@@ -238,7 +250,9 @@ module Lib_and_module = struct
238250
Action_builder.all
239251
(List.map ts ~f:(function
240252
| Lib t ->
241-
let+ p = Action_builder.of_memo (Link_params.get sctx t mode) in
253+
let+ p =
254+
Action_builder.of_memo (Link_params.get sctx t mode lib_config)
255+
in
242256
Command.Args.S
243257
(Deps p.deps
244258
:: Hidden_deps (Dep.Set.of_files p.hidden_deps)

0 commit comments

Comments
 (0)