Skip to content

Commit 6187bd6

Browse files
authored
refactor: simpler tracking of Lib_info.virtual_ (#11713)
Signed-off-by: Antonio Nuno Monteiro <[email protected]>
1 parent 5666e7c commit 6187bd6

File tree

9 files changed

+39
-44
lines changed

9 files changed

+39
-44
lines changed

src/dune_rules/dune_package.ml

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -105,7 +105,7 @@ module Lib = struct
105105
let melange_runtime_deps = additional_paths (Lib_info.melange_runtime_deps info) in
106106
let jsoo_runtime = Lib_info.jsoo_runtime info in
107107
let wasmoo_runtime = Lib_info.wasmoo_runtime info in
108-
let virtual_ = Option.is_some (Lib_info.virtual_ info) in
108+
let virtual_ = Lib_info.virtual_ info in
109109
let instrumentation_backend = Lib_info.instrumentation_backend info in
110110
let native_archives =
111111
match Lib_info.native_archives info with
@@ -247,9 +247,6 @@ module Lib = struct
247247
let preprocess = Preprocess.Per_module.no_preprocessing () in
248248
let virtual_deps = [] in
249249
let dune_version = None in
250-
let virtual_ =
251-
if virtual_ then Some (Lib_info.Source.External modules) else None
252-
in
253250
let entry_modules = Modules.entry_modules modules |> List.map ~f:Module.name in
254251
let modules = Modules.With_vlib.modules modules in
255252
let wrapped =

src/dune_rules/findlib.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -168,7 +168,7 @@ let to_dune_library (t : Findlib.Package.t) ~dir_contents ~ext_lib ~external_loc
168168
let wasmoo_runtime = Findlib.Package.wasmoo_runtime t in
169169
let melange_runtime_deps = Lib_info.File_deps.External [] in
170170
let preprocess = Preprocess.Per_module.no_preprocessing () in
171-
let virtual_ = None in
171+
let virtual_ = false in
172172
let default_implementation = None in
173173
let wrapped = None in
174174
let foreign_archives, native_archives =

src/dune_rules/install_rules.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -98,8 +98,8 @@ end = struct
9898
>>| Option.some
9999
and+ foreign_archives =
100100
match Lib_info.virtual_ lib with
101-
| None -> Memo.return (Mode.Map.Multi.to_flat_list @@ Lib_info.foreign_archives lib)
102-
| Some _ ->
101+
| false -> Memo.return (Mode.Map.Multi.to_flat_list @@ Lib_info.foreign_archives lib)
102+
| true ->
103103
let+ foreign_sources = Dir_contents.foreign_sources dir_contents in
104104
let name = Lib_info.name lib in
105105
let files = Foreign_sources.for_lib foreign_sources ~name in
@@ -823,7 +823,7 @@ end = struct
823823
match
824824
List.find_map libraries ~f:(fun lib ->
825825
let info = Lib.Local.info lib in
826-
Option.some_if (Option.is_some (Lib_info.virtual_ info)) lib)
826+
Option.some_if (Lib_info.virtual_ info) lib)
827827
with
828828
| None -> Action_builder.lines_of meta_template
829829
| Some vlib ->

src/dune_rules/lib.ml

Lines changed: 11 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -688,14 +688,14 @@ end = struct
688688
let add t lib =
689689
let virtual_ = Lib_info.virtual_ lib.info in
690690
match lib.implements, virtual_ with
691-
| None, None -> Resolve.Memo.return t
692-
| Some _, Some _ -> assert false (* can't be virtual and implement *)
693-
| None, Some _ ->
691+
| None, false -> Resolve.Memo.return t
692+
| Some _, true -> assert false (* can't be virtual and implement *)
693+
| None, true ->
694694
Resolve.Memo.return
695695
(if Set.mem t.implemented lib
696696
then t
697697
else { t with unimplemented = Set.add t.unimplemented lib })
698-
| Some vlib, None ->
698+
| Some vlib, false ->
699699
let+ vlib = Memo.return vlib in
700700
{ implemented = Set.add t.implemented vlib
701701
; unimplemented = Set.remove t.unimplemented vlib
@@ -726,10 +726,10 @@ end = struct
726726
| (lib, stack) :: libs ->
727727
let virtual_ = Lib_info.virtual_ lib.info in
728728
(match lib.implements, virtual_ with
729-
| None, None -> loop acc libs
730-
| Some _, Some _ -> assert false (* can't be virtual and implement *)
731-
| None, Some _ -> loop (Map.set acc lib (No_impl stack)) libs
732-
| Some vlib, None ->
729+
| None, false -> loop acc libs
730+
| Some _, true -> assert false (* can't be virtual and implement *)
731+
| None, true -> loop (Map.set acc lib (No_impl stack)) libs
732+
| Some vlib, false ->
733733
let* vlib = Memo.return vlib in
734734
(match Map.find acc vlib with
735735
| None ->
@@ -948,8 +948,8 @@ end = struct
948948
let* vlib = resolve_forbid_ignore name in
949949
let virtual_ = Lib_info.virtual_ vlib.info in
950950
match virtual_ with
951-
| None -> Error.not_virtual_lib ~loc ~impl:info ~not_vlib:vlib.info
952-
| Some _ -> Resolve.Memo.return vlib
951+
| false -> Error.not_virtual_lib ~loc ~impl:info ~not_vlib:vlib.info
952+
| true -> Resolve.Memo.return vlib
953953
in
954954
Memo.map res ~f:Option.some
955955
in
@@ -1616,8 +1616,7 @@ end = struct
16161616
in
16171617
(* If the library has an implementation according to variants or
16181618
default impl. *)
1619-
let virtual_ = Lib_info.virtual_ lib.info in
1620-
if Option.is_none virtual_
1619+
if not (Lib_info.virtual_ lib.info)
16211620
then R.return ()
16221621
else
16231622
let* impl = R.lift (impl_for lib) in

src/dune_rules/lib_info.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -324,7 +324,7 @@ type 'path t =
324324
; virtual_deps : (Loc.t * Lib_name.t) list
325325
; dune_version : Dune_lang.Syntax.Version.t option
326326
; sub_systems : Sub_system_info.t Sub_system_name.Map.t
327-
; virtual_ : Modules.t Source.t option
327+
; virtual_ : bool
328328
; entry_modules : (Module_name.t list, User_message.t) result Source.t
329329
; implements : (Loc.t * Lib_name.t) option
330330
; default_implementation : (Loc.t * Lib_name.t) option
@@ -597,7 +597,7 @@ let to_dyn
597597
; "virtual_deps", list (snd Lib_name.to_dyn) virtual_deps
598598
; "dune_version", option Dune_lang.Syntax.Version.to_dyn dune_version
599599
; "sub_systems", Sub_system_name.Map.to_dyn Dyn.opaque sub_systems
600-
; "virtual_", option (Source.to_dyn Modules.to_dyn) virtual_
600+
; "virtual_", bool virtual_
601601
; ( "entry_modules"
602602
, Source.to_dyn
603603
(Result.to_dyn (list Module_name.to_dyn) string)

src/dune_rules/lib_info.mli

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -139,7 +139,7 @@ val jsoo_runtime : 'path t -> 'path list
139139
val wasmoo_runtime : 'path t -> 'path list
140140
val melange_runtime_deps : 'path t -> 'path File_deps.t
141141
val obj_dir : 'path t -> 'path Obj_dir.t
142-
val virtual_ : _ t -> Modules.t Source.t option
142+
val virtual_ : _ t -> bool
143143
val entry_modules : _ t -> (Module_name.t list, User_message.t) result Source.t
144144
val main_module_name : _ t -> Main_module_name.t
145145
val wrapped : _ t -> Wrapped.t Inherited.t option
@@ -217,7 +217,7 @@ val create
217217
-> enabled:Enabled_status.t Memo.t
218218
-> virtual_deps:(Loc.t * Lib_name.t) list
219219
-> dune_version:Dune_lang.Syntax.Version.t option
220-
-> virtual_:Modules.t Source.t option
220+
-> virtual_:bool
221221
-> entry_modules:(Module_name.t list, User_message.t) result Source.t
222222
-> implements:(Loc.t * Lib_name.t) option
223223
-> default_implementation:(Loc.t * Lib_name.t) option

src/dune_rules/ml_sources.ml

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -328,8 +328,10 @@ let modules t ~libs ~for_ = modules_and_obj_dir t ~libs ~for_ >>| fst
328328
let virtual_modules ~lookup_vlib ~libs vlib =
329329
let info = Lib.info vlib in
330330
let+ modules =
331-
match Option.value_exn (Lib_info.virtual_ info) with
332-
| External modules -> Memo.return modules
331+
match Lib_info.modules info with
332+
| External modules ->
333+
let modules = Option.value_exn modules in
334+
Memo.return (Modules_group.With_vlib.drop_vlib modules)
333335
| Local ->
334336
let src_dir = Lib_info.src_dir info |> Path.as_in_build_dir_exn in
335337
let* t = lookup_vlib ~dir:src_dir in

src/dune_rules/stanzas/library.ml

Lines changed: 3 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -440,7 +440,7 @@ let to_lib_info
440440
| Private pkg -> Lib_info.Status.Private (conf.project, pkg)
441441
| Public p -> Public (conf.project, p.package)
442442
in
443-
let virtual_library = is_virtual conf in
443+
let virtual_ = is_virtual conf in
444444
let foreign_archives =
445445
let init =
446446
Mode.Map.Multi.create_for_all_modes
@@ -456,7 +456,7 @@ let to_lib_info
456456
in
457457
let native_archives =
458458
let archive = archive ext_lib in
459-
if virtual_library || not modes.ocaml.native
459+
if virtual_ || not modes.ocaml.native
460460
then Lib_info.Files []
461461
else if
462462
Option.is_some conf.implements
@@ -467,10 +467,9 @@ let to_lib_info
467467
in
468468
let foreign_dll_files = foreign_dll_files conf ~dir ~ext_dll in
469469
let exit_module = Option.bind conf.stdlib ~f:(fun x -> x.exit_module) in
470-
let virtual_ = Option.map conf.virtual_modules ~f:(fun _ -> Lib_info.Source.Local) in
471470
let foreign_objects = Lib_info.Source.Local in
472471
let archives, plugins =
473-
if virtual_library
472+
if virtual_
474473
then Mode.Dict.make_both [], Mode.Dict.make_both []
475474
else (
476475
let plugins =

src/dune_rules/virtual_rules.ml

Lines changed: 12 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -74,22 +74,20 @@ let impl sctx ~(lib : Library.t) ~scope =
7474
]
7575
| Some vlib ->
7676
let info = Lib.info vlib in
77-
let virtual_ =
78-
match Lib_info.virtual_ info with
79-
| Some v -> v
80-
| None ->
81-
User_error.raise
82-
~loc:lib.buildable.loc
83-
[ Pp.textf
84-
"Library %s isn't virtual and cannot be implemented"
85-
(Lib_name.to_string implements)
86-
]
87-
in
77+
if not (Lib_info.virtual_ info)
78+
then
79+
User_error.raise
80+
~loc:lib.buildable.loc
81+
[ Pp.textf
82+
"Library %s isn't virtual and cannot be implemented"
83+
(Lib_name.to_string implements)
84+
];
8885
let+ vlib_modules, vlib_foreign_objects =
89-
let foreign_objects = Lib_info.foreign_objects info in
90-
match virtual_, foreign_objects with
86+
match Lib_info.modules info, Lib_info.foreign_objects info with
87+
| External modules, External fa ->
88+
let modules = Option.value_exn modules in
89+
Memo.return (Modules.With_vlib.drop_vlib modules, fa)
9190
| External _, Local | Local, External _ -> assert false
92-
| External modules, External fa -> Memo.return (modules, fa)
9391
| Local, Local ->
9492
let name = Lib.name vlib in
9593
let vlib = Lib.Local.of_lib_exn vlib in

0 commit comments

Comments
 (0)