Skip to content

Commit

Permalink
don't add rules if lib stanza is disabled
Browse files Browse the repository at this point in the history
Signed-off-by: Javier Chávarri <javier.chavarri@gmail.com>
  • Loading branch information
jchavarri committed Feb 14, 2024
1 parent 7f19d29 commit ff91664
Show file tree
Hide file tree
Showing 7 changed files with 68 additions and 115 deletions.
7 changes: 5 additions & 2 deletions src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -112,8 +112,11 @@ end = struct
let+ () = toplevel_setup ~sctx ~dir ~toplevel in
empty_none
| Library.T lib ->
let* cctx, merlin = Lib_rules.rules lib ~sctx ~dir ~scope ~dir_contents ~expander in
Memo.return { empty_none with merlin; cctx = Some (lib.buildable.loc, cctx) }
let* available = Lib_rules.rules lib ~sctx ~dir ~scope ~dir_contents ~expander in
(match available with
| None -> Memo.return empty_none
| Some (cctx, merlin) ->
Memo.return { empty_none with merlin; cctx = Some (lib.buildable.loc, cctx) })
| Foreign.Library.T lib ->
Expander.eval_blang expander lib.enabled_if
>>= if_available (fun () ->
Expand Down
14 changes: 4 additions & 10 deletions src/dune_rules/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1993,7 +1993,7 @@ module DB = struct

let get_compile_info t ~allow_overlaps ~dir name =
let open Memo.O in
find_even_when_hidden t name
find t name
>>| function
| Some lib ->
(match Local.of_lib lib with
Expand All @@ -2003,15 +2003,9 @@ module DB = struct
[ "name", Lib_name.to_dyn name ]
| Some info ->
(match Path.Build.equal dir (Lib_info.src_dir (Local.info info)) with
| true -> lib, Compile.for_lib ~allow_overlaps t lib
| false ->
Code_error.raise
"Lib.DB.get_compile_info got library that doesn't match build dir"
[ "name", Lib_name.to_dyn name; "dir", Path.Build.to_dyn dir ]))
| None ->
Code_error.raise
"Lib.DB.get_compile_info got library that doesn't exist"
[ "name", Lib_name.to_dyn name ]
| true -> Some (lib, Compile.for_lib ~allow_overlaps t lib)
| false -> None))
| None -> None
;;

let resolve_user_written_deps
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -141,7 +141,7 @@ module DB : sig
-> allow_overlaps:bool
-> dir:Path.Build.t
-> Lib_name.t
-> (lib * Compile.t) Memo.t
-> (lib * Compile.t) option Memo.t

val resolve : t -> Loc.t * Lib_name.t -> lib Resolve.Memo.t

Expand Down
52 changes: 29 additions & 23 deletions src/dune_rules/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -642,35 +642,41 @@ let library_rules

let rules (lib : Library.t) ~sctx ~dir_contents ~dir ~expander ~scope =
let buildable = lib.buildable in
let* local_lib, compile_info =
let* available =
Lib.DB.get_compile_info
(Scope.libs scope)
(Library.best_name lib)
~allow_overlaps:buildable.allow_overlapping_dependencies
~dir
in
let local_lib = Lib.Local.of_lib_exn local_lib in
let f () =
let* source_modules =
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules ~for_:(Library (Library.best_name lib))
match available with
| None -> Memo.return None
| Some (local_lib, compile_info) ->
let local_lib = Lib.Local.of_lib_exn local_lib in
let f () =
let* source_modules =
Dir_contents.ocaml dir_contents
>>| Ml_sources.modules ~for_:(Library (Library.best_name lib))
in
let* cctx = cctx lib ~sctx ~source_modules ~dir ~scope ~expander ~compile_info in
let* () =
match buildable.ctypes with
| None -> Memo.return ()
| Some _ ->
Ctypes_rules.gen_rules ~loc:(fst lib.name) ~cctx ~buildable ~sctx ~scope ~dir
in
library_rules
lib
~local_lib
~cctx
~source_modules
~dir_contents
~compile_info
~ctx_dir:dir
in
let* cctx = cctx lib ~sctx ~source_modules ~dir ~scope ~expander ~compile_info in
let* () =
match buildable.ctypes with
| None -> Memo.return ()
| Some _ ->
Ctypes_rules.gen_rules ~loc:(fst lib.name) ~cctx ~buildable ~sctx ~scope ~dir
let* () = Buildable_rules.gen_select_rules sctx compile_info ~dir in
let* res =
Buildable_rules.with_lib_deps (Super_context.context sctx) compile_info ~dir ~f
in
library_rules
lib
~local_lib
~cctx
~source_modules
~dir_contents
~compile_info
~ctx_dir:dir
in
let* () = Buildable_rules.gen_select_rules sctx compile_info ~dir in
Buildable_rules.with_lib_deps (Super_context.context sctx) compile_info ~dir ~f
Memo.return (Some res)
;;
2 changes: 1 addition & 1 deletion src/dune_rules/lib_rules.mli
Original file line number Diff line number Diff line change
Expand Up @@ -15,4 +15,4 @@ val rules
-> dir:Path.Build.t
-> expander:Expander.t
-> scope:Scope.t
-> (Compilation_context.t * Merlin.t option) Memo.t
-> (Compilation_context.t * Merlin.t option) option Memo.t
31 changes: 17 additions & 14 deletions src/dune_rules/top_module.ml
Original file line number Diff line number Diff line change
Expand Up @@ -43,29 +43,32 @@ let find_module sctx src =
| Some stanza ->
let* scope = Scope.DB.find_by_dir dir in
let* expander = Super_context.expander sctx ~dir in
let+ cctx, merlin =
let* available =
drop_rules
@@ fun () ->
match stanza with
| `Executables exes ->
let* cctx, merlin =
Exe_rules.rules ~sctx ~dir ~dir_contents ~scope ~expander exes
in
Memo.return (cctx, Some merlin)
Memo.return (Some (cctx, Some merlin))
| `Library lib -> Lib_rules.rules lib ~sctx ~dir ~scope ~dir_contents ~expander
in
let modules = Compilation_context.modules cctx in
let module_ =
match Modules.find modules module_name with
| Some m -> m
| None ->
User_error.raise
[ Pp.textf
"Could not find module corresponding to source file %s"
(Path.Build.to_string_maybe_quoted src)
]
in
Some (module_, cctx, merlin))
(match available with
| None -> Memo.return None
| Some (cctx, merlin) ->
let modules = Compilation_context.modules cctx in
let module_ =
match Modules.find modules module_name with
| Some m -> m
| None ->
User_error.raise
[ Pp.textf
"Could not find module corresponding to source file %s"
(Path.Build.to_string_maybe_quoted src)
]
in
Memo.return (Some (module_, cctx, merlin))))
;;

let module_deps cctx module_ =
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,17 @@ is not possible at the moment
> let x = "foo"
> EOF

$ dune build
$ dune build --display=short
ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt} [alt-context]
ocamlc .foo.objs/byte/foo.{cmi,cmo,cmt}
ocamlopt .foo.objs/native/foo.{cmx,o} [alt-context]
ocamlc foo.cma [alt-context]
ocamlopt .foo.objs/native/foo.{cmx,o}
ocamlc foo.cma
ocamlopt foo.{a,cmxa} [alt-context]
ocamlopt foo.{a,cmxa}
ocamlopt foo.cmxs [alt-context]
ocamlopt foo.cmxs

For public libraries

Expand Down Expand Up @@ -62,48 +72,6 @@ In the same context
If no public lib is available, the build finishes fine as there are no consumers of the libraries

$ dune build
Internal error, please report upstream including the contents of _build/log.
Description:
("Lib.DB.get_compile_info got library that doesn't exist",
{ name = "foo" })
Raised at Stdune__Code_error.raise in file
"otherlibs/stdune/src/code_error.ml", line 10, characters 30-62
Called from Fiber__Core.O.(>>|).(fun) in file "vendor/fiber/src/core.ml",
line 253, characters 36-41
Called from Fiber__Core.apply2 in file "vendor/fiber/src/core.ml", line 92,
characters 6-11
Re-raised at Stdune__Exn.raise_with_backtrace in file
"otherlibs/stdune/src/exn.ml", line 38, characters 27-56
Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml",
line 76, characters 8-11
Re-raised at Stdune__Exn.raise_with_backtrace in file
"otherlibs/stdune/src/exn.ml", line 38, characters 27-56
Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml",
line 76, characters 8-11
Re-raised at Stdune__Exn.raise_with_backtrace in file
"otherlibs/stdune/src/exn.ml", line 38, characters 27-56
Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml",
line 76, characters 8-11
Re-raised at Stdune__Exn.raise_with_backtrace in file
"otherlibs/stdune/src/exn.ml", line 38, characters 27-56
Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml",
line 76, characters 8-11
Re-raised at Stdune__Exn.raise_with_backtrace in file
"otherlibs/stdune/src/exn.ml", line 38, characters 27-56
Called from Fiber__Scheduler.exec in file "vendor/fiber/src/scheduler.ml",
line 76, characters 8-11
-> required by ("<unnamed>", ())
-> required by ("load-dir", In_build_dir "alt-context")
-> required by
("build-alias", { dir = In_build_dir "alt-context"; name = "default" })
-> required by ("toplevel", ())

I must not crash. Uncertainty is the mind-killer. Exceptions are the
little-death that brings total obliteration. I will fully express my cases.
Execution will pass over me and through me. And when it has gone past, I
will unwind the stack along its path. Where the cases are handled there will
be nothing. Only I will remain.
[1]

Let's add an exe to consume the library to trigger the error

Expand All @@ -122,27 +90,6 @@ Let's add an exe to consume the library to trigger the error
> EOF

$ dune build
Internal error, please report upstream including the contents of _build/log.
Description:
("Lib.DB.get_compile_info got library that doesn't exist",
{ name = "foo" })
Raised at Stdune__Code_error.raise in file
"otherlibs/stdune/src/code_error.ml", line 10, characters 30-62
Called from Fiber__Core.O.(>>|).(fun) in file "vendor/fiber/src/core.ml",
line 253, characters 36-41
Called from Fiber__Core.apply2 in file "vendor/fiber/src/core.ml", line 92,
characters 6-11
-> required by ("<unnamed>", ())
-> required by ("load-dir", In_build_dir "alt-context")
-> required by
("build-alias", { dir = In_build_dir "alt-context"; name = "default" })
-> required by ("toplevel", ())

I must not crash. Uncertainty is the mind-killer. Exceptions are the
little-death that brings total obliteration. I will fully express my cases.
Execution will pass over me and through me. And when it has gone past, I
will unwind the stack along its path. Where the cases are handled there will
be nothing. Only I will remain.
File "dune", line 3, characters 0-21:
3 | (library
4 | (name foo))
Expand Down

0 comments on commit ff91664

Please sign in to comment.