Skip to content

Commit

Permalink
Remove force_alias_module
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Nov 20, 2020
1 parent 8e881dd commit 5c9e276
Show file tree
Hide file tree
Showing 3 changed files with 11 additions and 24 deletions.
9 changes: 3 additions & 6 deletions src/dune_rules/ml_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -208,7 +208,7 @@ let virtual_modules lookup_vlib vlib =
}

let make_lib_modules (d : _ Dir_with_dune.t) ~lookup_vlib ~(lib : Library.t)
~modules ~force_alias_module =
~modules =
let src_dir = d.ctx_dir in
let kind, main_module_name, wrapped =
match lib.implements with
Expand Down Expand Up @@ -274,16 +274,13 @@ let make_lib_modules (d : _ Dir_with_dune.t) ~lookup_vlib ~(lib : Library.t)
let implements = Option.is_some lib.implements in
let _loc, lib_name = lib.name in
Modules_group.lib ~stdlib ~implements ~lib_name ~src_dir ~modules
~main_module_name ~wrapped ~force_alias_module
~main_module_name ~wrapped

let libs_and_exes (d : _ Dir_with_dune.t) ~lookup_vlib ~modules =
List.filter_partition_map d.data ~f:(fun stanza ->
match (stanza : Stanza.t) with
| Library lib ->
let modules =
make_lib_modules d ~lookup_vlib ~modules ~lib
~force_alias_module:false
in
let modules = make_lib_modules d ~lookup_vlib ~modules ~lib in
Left (lib, modules)
| Executables exes
| Tests { exes; _ } ->
Expand Down
23 changes: 8 additions & 15 deletions src/dune_rules/modules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -480,7 +480,7 @@ let rec main_module_name = function
| Impl { vlib; impl = _ } -> main_module_name vlib

let lib ~src_dir ~main_module_name ~wrapped ~stdlib ~lib_name ~implements
~modules ~force_alias_module =
~modules =
let make_wrapped main_module_name =
Wrapped
(Wrapped.make ~src_dir ~lib_name ~implements ~modules ~main_module_name
Expand All @@ -491,24 +491,17 @@ let lib ~src_dir ~main_module_name ~wrapped ~stdlib ~lib_name ~implements
let main_module_name = Option.value_exn main_module_name in
Stdlib (Stdlib.make ~stdlib ~modules ~main_module_name)
| None -> (
match
(wrapped, main_module_name, as_singleton modules, force_alias_module)
with
| Simple false, _, _, true ->
Code_error.raise "Modules.lib: unwrapped and force_alias" []
| Simple false, _, Some m, false -> Singleton m
| Simple false, _, None, false -> Unwrapped modules
| (Yes_with_transition _ | Simple true), Some main_module_name, Some m, _ ->
if
Module.name m = main_module_name
&& (not implements) && not force_alias_module
then
match (wrapped, main_module_name, as_singleton modules) with
| Simple false, _, Some m -> Singleton m
| Simple false, _, None -> Unwrapped modules
| (Yes_with_transition _ | Simple true), Some main_module_name, Some m ->
if Module.name m = main_module_name && not implements then
Singleton m
else
make_wrapped main_module_name
| (Yes_with_transition _ | Simple true), Some main_module_name, None, _ ->
| (Yes_with_transition _ | Simple true), Some main_module_name, None ->
make_wrapped main_module_name
| (Simple true | Yes_with_transition _), None, _, _ ->
| (Simple true | Yes_with_transition _), None, _ ->
Code_error.raise "Modules.lib: cannot wrap without main module name" [] )

let impl impl ~vlib =
Expand Down
3 changes: 0 additions & 3 deletions src/dune_rules/modules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -15,9 +15,6 @@ val lib :
-> lib_name:Lib_name.Local.t
-> implements:bool
-> modules:Module.Name_map.t
-> force_alias_module:bool
(** Force the creation of an alias module. Required if we're renaming any
dependencies *)
-> t

val encode : t -> Dune_lang.t
Expand Down

0 comments on commit 5c9e276

Please sign in to comment.