File tree Expand file tree Collapse file tree 5 files changed +29
-9
lines changed
Expand file tree Collapse file tree 5 files changed +29
-9
lines changed Original file line number Diff line number Diff line change @@ -5,7 +5,7 @@ module SC = Super_context
55module Includes = struct
66 type t = string list Arg_spec .t Cm_kind.Dict .t
77
8- let make sctx ~opaque ~ requires : _ Cm_kind.Dict. t =
8+ let make sctx ~requires : _ Cm_kind.Dict. t =
99 match requires with
1010 | Error exn -> Cm_kind.Dict. make_all (Arg_spec. Dyn (fun _ -> raise exn ))
1111 | Ok libs ->
@@ -19,13 +19,18 @@ module Includes = struct
1919 ]
2020 in
2121 let cmx_includes =
22- if opaque then
23- cmi_includes
24- else
25- Arg_spec. S [ iflags
26- ; Hidden_deps
27- (SC.Libs. file_deps sctx libs ~ext: " .cmi-and-.cmx" )
28- ]
22+ Arg_spec. S
23+ [ iflags
24+ ; Hidden_deps
25+ ( libs
26+ |> List. map ~f: (fun lib ->
27+ (lib, if Lib. opaque lib then
28+ " .cmi"
29+ else
30+ " .cmi-and-.cmx" ))
31+ |> SC.Libs. file_deps_with_exts sctx
32+ )
33+ ]
2934 in
3035 { cmi = cmi_includes
3136 ; cmo = cmi_includes
@@ -84,7 +89,7 @@ let create ~super_context ~scope ~dir ?(dir_kind=File_tree.Dune_file.Kind.Dune)
8489 ; lib_interface_module
8590 ; flags
8691 ; requires
87- ; includes = Includes. make super_context ~requires ~opaque
92+ ; includes = Includes. make super_context ~requires
8893 ; preprocessing
8994 ; no_keep_locs
9095 ; opaque
Original file line number Diff line number Diff line change @@ -338,6 +338,8 @@ let plugins t = t.info.plugins
338338let jsoo_runtime t = t.info.jsoo_runtime
339339let unique_id t = t.unique_id
340340
341+ let opaque t = t.info.opaque
342+
341343let dune_version t = t.info.dune_version
342344
343345let src_dir t = t.info.src_dir
Original file line number Diff line number Diff line change @@ -26,6 +26,8 @@ val archives : t -> Path.t list Mode.Dict.t
2626val plugins : t -> Path .t list Mode.Dict .t
2727val jsoo_runtime : t -> Path .t list
2828
29+ val opaque : t -> bool
30+
2931val dune_version : t -> Syntax.Version .t option
3032
3133(* * A unique integer identifier. It is only unique for the duration of
Original file line number Diff line number Diff line change @@ -708,6 +708,15 @@ module Libs = struct
708708 (lib_files_alias ~dir ~name: (Library. best_name lib) ~ext ))
709709 |> Path.Set. of_list)
710710
711+ let file_deps_with_exts t lib_exts =
712+ List. rev_map lib_exts ~f: (fun ((lib : Lib.t ), ext ) ->
713+ if Lib. is_local lib then
714+ Alias. stamp_file
715+ (lib_files_alias ~dir: (Lib. src_dir lib) ~name: (Lib. name lib) ~ext )
716+ else
717+ Build_system. stamp_file_for_files_of t.build_system
718+ ~dir: (Lib. obj_dir lib) ~ext )
719+
711720 let file_deps t libs ~ext =
712721 List. rev_map libs ~f: (fun (lib : Lib.t ) ->
713722 if Lib. is_local lib then
Original file line number Diff line number Diff line change @@ -197,6 +197,8 @@ module Libs : sig
197197 all the files with extension [ext] of libraries [libs]. *)
198198 val file_deps : t -> Lib .L .t -> ext :string -> Path .t list
199199
200+ val file_deps_with_exts : t -> (Lib .t * string ) list -> Path .t list
201+
200202 (* * Setup the alias that depends on all files with a given extension
201203 for a library *)
202204 val setup_file_deps_alias
You can’t perform that action at this time.
0 commit comments