Skip to content

Commit

Permalink
Revert "Generate dummy modules"
Browse files Browse the repository at this point in the history
This reverts commit 3ecfd8bd5f13bc0252e771dae599822babafa67b.

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Dec 18, 2020
1 parent 40f5e8d commit 6d392ca
Show file tree
Hide file tree
Showing 5 changed files with 94 additions and 5,258 deletions.
28 changes: 2 additions & 26 deletions src/dune_rules/ml_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -203,29 +203,6 @@ let virtual_modules lookup_vlib vlib =
; allow_new_public_modules
}

let add_dummy_module_if_needed modules ~src_dir ~(lib : Library.t) =
let at_least_one_impl =
Module_name.Map.exists modules ~f:(Module.has ~ml_kind:Impl)
in
if at_least_one_impl then
modules
else
let name =
let prefix =
let pkg =
match lib.visibility with
| Private pkg -> pkg
| Public p -> Some (Dune_file.Public_lib.package p)
in
match pkg with
| None -> Lib_name.Local.to_string (snd lib.name)
| Some pkg -> Package.Name.to_string (Package.name pkg)
in
Module_name.of_string (prefix ^ "_dummy")
in
let module_ = Module.generated_dummy ~src_dir name in
Module_name.Map.add_exn modules name module_

let make_lib_modules (d : _ Dir_with_dune.t) ~lookup_vlib ~(lib : Library.t)
~modules =
let src_dir = d.ctx_dir in
Expand Down Expand Up @@ -271,8 +248,8 @@ let make_lib_modules (d : _ Dir_with_dune.t) ~lookup_vlib ~(lib : Library.t)
in
let+ main_module_name, wrapped =
let open Result.O in
let+ main_module_name = Lib.main_module_name resolved
and+ wrapped = Lib.wrapped resolved in
let* main_module_name = Lib.main_module_name resolved in
let+ wrapped = Lib.wrapped resolved in
(main_module_name, Option.value_exn wrapped)
in
(kind, main_module_name, wrapped)
Expand All @@ -282,7 +259,6 @@ let make_lib_modules (d : _ Dir_with_dune.t) ~lookup_vlib ~(lib : Library.t)
~private_modules:
(Option.value ~default:Ordered_set_lang.standard lib.private_modules)
~src_dir
|> add_dummy_module_if_needed ~src_dir ~lib
in
let stdlib = lib.stdlib in
let implements = Option.is_some lib.implements in
Expand Down
9 changes: 0 additions & 9 deletions src/dune_rules/module.ml
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ module Kind = struct
| Impl_vmodule
| Wrapped_compat
| Root
| Dummy

let to_string = function
| Intf_only -> "intf_only"
Expand All @@ -40,7 +39,6 @@ module Kind = struct
| Impl_vmodule -> "impl_vmodule"
| Wrapped_compat -> "wrapped_compat"
| Root -> "root"
| Dummy -> "dummy"

let to_dyn t = Dyn.Encoder.string (to_string t)

Expand All @@ -63,7 +61,6 @@ module Kind = struct
| Impl_vmodule
| Wrapped_compat
| Root
| Dummy
| Impl ->
true
| Intf_only
Expand Down Expand Up @@ -261,7 +258,6 @@ let encode
| Alias
| Impl
| Virtual
| Dummy
| Intf_only ->
Some kind
in
Expand Down Expand Up @@ -348,11 +344,6 @@ let generated_root ~src_dir name =
let t = generated ~src_dir name in
{ t with kind = Root; visibility = Private }

let generated_dummy ~src_dir name =
let src_dir = Path.build src_dir in
let t = generated ~src_dir name in
{ t with kind = Dummy; visibility = Private }

let of_source ~visibility ~kind source = of_source ~visibility ~kind source

module Name_map = struct
Expand Down
3 changes: 0 additions & 3 deletions src/dune_rules/module.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ module Kind : sig
| Impl_vmodule
| Wrapped_compat
| Root
| Dummy

include Dune_lang.Conv.S with type t := t
end
Expand Down Expand Up @@ -136,5 +135,3 @@ val generated : src_dir:Path.t -> Module_name.t -> t
val generated_alias : src_dir:Path.Build.t -> Module_name.t -> t

val generated_root : src_dir:Path.Build.t -> Module_name.t -> t

val generated_dummy : src_dir:Path.Build.t -> Module_name.t -> t
11 changes: 0 additions & 11 deletions src/dune_rules/module_compilation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -326,14 +326,6 @@ let build_alias_module ~alias_module ~cctx =
build_module cctx alias_module
~dep_graphs:(Dep_graph.Ml_kind.dummy alias_module)

let build_dummy_module module_ ~cctx =
let sctx = Compilation_context.super_context cctx in
let file = Option.value_exn (Module.file module_ ~ml_kind:Impl) in
let dir = Compilation_context.dir cctx in
Super_context.add_rule ~loc:Loc.none sctx ~dir
(Build.write_file (Path.as_in_build_dir_exn file) "");
build_module cctx module_ ~dep_graphs:(Dep_graph.Ml_kind.dummy module_)

let root_source entries =
let b = Buffer.create 128 in
List.iter entries ~f:(fun name ->
Expand Down Expand Up @@ -366,9 +358,6 @@ let build_all cctx ~dep_graphs =
| Alias ->
let cctx = Compilation_context.for_alias_module cctx in
build_alias_module ~alias_module:m ~cctx
| Dummy ->
let cctx = Compilation_context.for_alias_module cctx in
build_dummy_module m ~cctx
| Wrapped_compat ->
let cctx = Lazy.force for_wrapped_compat in
build_module cctx ~dep_graphs m
Expand Down
Loading

0 comments on commit 6d392ca

Please sign in to comment.