@@ -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 ;;
7777end
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 ;;
224236end
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