Skip to content

Commit

Permalink
Merge branch 'main' into improve-ml-sources-same-folder-collision
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 Mar 10, 2024
2 parents ef6c146 + 6a2c7af commit 74bca3f
Show file tree
Hide file tree
Showing 6 changed files with 92 additions and 94 deletions.
4 changes: 2 additions & 2 deletions src/dune_rules/action_unexpanded.ml
Original file line number Diff line number Diff line change
Expand Up @@ -404,8 +404,8 @@ end = struct
if Dune_project.dune_version project >= (3, 14)
then Artifacts.Original_path
else Install_dir
in
Artifacts.binary ~loc:(Some loc) ~where (Expander.artifacts env.expander) s)
and* artifacts = Expander.artifacts env.expander in
Artifacts.binary ~loc:(Some loc) ~where artifacts s)
in
let prog = Result.map prog ~f:(Expander.map_exe env.expander) in
let args = Value.L.to_strings ~dir args in
Expand Down
3 changes: 1 addition & 2 deletions src/dune_rules/env_node.ml
Original file line number Diff line number Diff line change
Expand Up @@ -58,8 +58,7 @@ let make
in
let artifacts =
inherited ~field:artifacts ~root:default_artifacts (fun binaries ->
let+ local_binaries = Memo.Lazy.force local_binaries in
Artifacts.add_binaries binaries ~dir local_binaries)
Memo.Lazy.force local_binaries >>| Artifacts.add_binaries binaries ~dir)
in
{ external_env; artifacts; local_binaries }
;;
145 changes: 73 additions & 72 deletions src/dune_rules/expander.ml
Original file line number Diff line number Diff line change
Expand Up @@ -50,9 +50,9 @@ type t =
{ dir : Path.Build.t
; env : Env.t Memo.t
; local_env : string Action_builder.t Env.Var.Map.t
; public_libs : Lib.DB.t
; public_libs_host : Lib.DB.t
; artifacts_host : Artifacts.t
; public_libs : Lib.DB.t Memo.t
; public_libs_host : Lib.DB.t Memo.t
; artifacts_host : Artifacts.t Memo.t
; bindings : value Pform.Map.t
; scope : Scope.t
; scope_host : Scope.t
Expand Down Expand Up @@ -347,74 +347,68 @@ let expand_lib_variable t source ~lib ~file ~lib_exec ~lib_private =
then t.public_libs_host, Context.host t.context
else t.public_libs, Memo.return t.context
in
let* artifacts = Resolve.Memo.lift_memo artifacts in
file_of_lib artifacts context ~loc ~lib ~file)
in
let p =
let open Memo.O in
Resolve.Memo.peek p
>>| function
| Ok p ->
(match file with
| "" | "." ->
let lang_version = Dune_project.dune_version (Scope.project t.scope) in
if lang_version < (3, 0)
then Action_builder.return [ Value.Path p ]
else
User_error.raise
~loc
[ Pp.textf
"The form %%{%s:<libname>:%s} is no longer supported since version 3.0 \
of the Dune language."
(if lib_private then "lib-private" else "lib")
file
]
~hints:
[ (match Lib_name.to_string lib with
| "ctypes" ->
Pp.text
"Did you know that Dune 3.0 supports ctypes natively? See the \
manual for more details."
| _ ->
Pp.textf
"If you are trying to use this form to include a directory, you \
should instead use (foreign_stubs (include_dirs (lib %s))). See \
the manual for more details."
(Lib_name.to_string lib))
]
| _ ->
if (not lib_exec) || (not Sys.win32) || Filename.extension file = ".exe"
then dep p
else (
let p_exe = Path.extend_basename p ~suffix:".exe" in
Action_builder.if_file_exists p_exe ~then_:(dep p_exe) ~else_:(dep p)))
| Error () ->
let p =
if lib_private
then Resolve.Memo.map p ~f:(fun _ -> assert false)
(let open Memo.O in
Resolve.Memo.peek p
>>| function
| Ok p ->
(match file with
| "" | "." ->
if Dune_project.dune_version (Scope.project t.scope) < (3, 0)
then Action_builder.return [ Value.Path p ]
else
let open Resolve.Memo.O in
let* available =
Resolve.Memo.lift_memo (Lib.DB.available (Scope.libs scope) lib)
in
match available with
| false ->
let+ _ = p in
assert false
| true ->
Resolve.Memo.fail
(User_error.make
~loc
[ Pp.textf
"The library %S is not public. The variable \"lib%s\" expands to \
the file's installation path which is not defined for private \
libraries."
(Lib_name.to_string lib)
(if lib_exec then "exec" else "")
])
in
Resolve.Memo.read p
in
Action_builder.of_memo_join p
User_error.raise
~loc
[ Pp.textf
"The form %%{%s:<libname>:%s} is no longer supported since version 3.0 \
of the Dune language."
(if lib_private then "lib-private" else "lib")
file
]
~hints:
[ (match Lib_name.to_string lib with
| "ctypes" ->
Pp.text
"Did you know that Dune 3.0 supports ctypes natively? See the \
manual for more details."
| _ ->
Pp.textf
"If you are trying to use this form to include a directory, you \
should instead use (foreign_stubs (include_dirs (lib %s))). See \
the manual for more details."
(Lib_name.to_string lib))
]
| _ ->
if (not lib_exec) || (not Sys.win32) || Filename.extension file = ".exe"
then dep p
else (
let p_exe = Path.extend_basename p ~suffix:".exe" in
Action_builder.if_file_exists p_exe ~then_:(dep p_exe) ~else_:(dep p)))
| Error () ->
(if lib_private
then Resolve.Memo.map p ~f:(fun _ -> assert false)
else
let open Resolve.Memo.O in
Lib.DB.available (Scope.libs scope) lib
|> Resolve.Memo.lift_memo
>>= function
| false ->
let+ (_ : Path.t) = p in
assert false
| true ->
Resolve.Memo.fail
(User_error.make
~loc
[ Pp.textf
"The library %S is not public. The variable \"lib%s\" expands to the \
file's installation path which is not defined for private libraries."
(Lib_name.to_string lib)
(if lib_exec then "exec" else "")
]))
|> Resolve.Memo.read)
|> Action_builder.of_memo_join
;;

let make loc context =
Expand Down Expand Up @@ -624,9 +618,11 @@ let expand_pform_macro
With
(let* prog =
Action_builder.of_memo
(Artifacts.binary
(let open Memo.O in
let* artifacts_host = t.artifacts_host in
Artifacts.binary
~loc:(Some (Dune_lang.Template.Pform.loc source))
t.artifacts_host
artifacts_host
s)
in
dep (Action.Prog.ok_exn prog)))
Expand All @@ -652,7 +648,8 @@ let expand_pform_macro
(fun t ->
Without
(let open Memo.O in
let+ b = Artifacts.binary_available t.artifacts_host s in
let* artifacts_host = t.artifacts_host in
let+ b = Artifacts.binary_available artifacts_host s in
b |> string_of_bool |> string))
| Read -> expand_read_macro ~dir ~source s ~read:string
| Read_lines ->
Expand All @@ -672,7 +669,11 @@ let expand_pform_macro
|> strings)
| Coq_config ->
Need_full_expander
(fun t -> Without (Coq_config.expand source macro_invocation t.artifacts_host))
(fun t ->
Without
(let open Memo.O in
let* artifacts_host = t.artifacts_host in
Coq_config.expand source macro_invocation artifacts_host))
;;

let expand_pform_gen ~(context : Context.t) ~bindings ~dir ~source (pform : Pform.t)
Expand Down
10 changes: 5 additions & 5 deletions src/dune_rules/expander.mli
Original file line number Diff line number Diff line change
Expand Up @@ -12,15 +12,15 @@ val make_root
-> scope_host:Scope.t
-> context:Context.t
-> env:Env.t Memo.t
-> public_libs:Lib.DB.t
-> public_libs_host:Lib.DB.t
-> artifacts_host:Artifacts.t
-> public_libs:Lib.DB.t Memo.t
-> public_libs_host:Lib.DB.t Memo.t
-> artifacts_host:Artifacts.t Memo.t
-> t

val set_local_env_var : t -> var:string -> value:string Action_builder.t -> t
val set_dir : t -> dir:Path.Build.t -> t
val set_scope : t -> scope:Scope.t -> scope_host:Scope.t -> t
val set_artifacts : t -> artifacts_host:Artifacts.t -> t
val set_artifacts : t -> artifacts_host:Artifacts.t Memo.t -> t

module Expanding_what : sig
type t =
Expand Down Expand Up @@ -107,7 +107,7 @@ val expand_and_eval_set

val eval_blang : t -> Blang.t -> bool Memo.t
val map_exe : t -> Path.t -> Path.t
val artifacts : t -> Artifacts.t
val artifacts : t -> Artifacts.t Memo.t
val expand_locks : t -> Locks.t -> Path.t list Action_builder.t

val foreign_flags
Expand Down
19 changes: 8 additions & 11 deletions src/dune_rules/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ type t =
; default_env : Env_node.t Memo.Lazy.t
; host : t option
; root_expander : Expander.t
; artifacts : Artifacts.t
; artifacts : Artifacts.t Memo.t
; get_node : Path.Build.t -> Env_node.t Memo.t
}

Expand Down Expand Up @@ -51,8 +51,8 @@ let expander_for_artifacts t ~dir =
;;

let expander t ~dir =
let* expander_for_artifacts = expander_for_artifacts t ~dir in
let+ artifacts_host = artifacts_host t ~dir in
let+ expander_for_artifacts = expander_for_artifacts t ~dir in
let artifacts_host = artifacts_host t ~dir in
Expander.set_artifacts expander_for_artifacts ~artifacts_host
;;

Expand Down Expand Up @@ -96,7 +96,7 @@ let get_impl t dir =
~profile
~expander
~default_env:t.context_env
~default_artifacts:(Memo.return t.artifacts)
~default_artifacts:t.artifacts
;;

(* Here we jump through some hoops to construct [t] as well as create a
Expand Down Expand Up @@ -195,7 +195,7 @@ let make_default_env_node
profile
(env_nodes : Context.Env_nodes.t)
~root_env
~(artifacts : Artifacts.t)
~artifacts
=
let make ~inherit_from ~config_stanza =
let config_stanza = Option.value config_stanza ~default:Dune_env.empty in
Expand All @@ -212,7 +212,7 @@ let make_default_env_node
~profile
~expander
~default_env:root_env
~default_artifacts:(Memo.return artifacts)
~default_artifacts:artifacts
in
make
~config_stanza:env_nodes.context
Expand Down Expand Up @@ -270,9 +270,6 @@ let create ~(context : Context.t) ~(host : t option) ~packages ~stanzas =
artifacts, public_libs, host
in
let+ scope = Scope.DB.find_by_dir (Context.build_dir context)
and+ public_libs = public_libs
and+ artifacts_host = artifacts_host
and+ public_libs_host = public_libs_host
and+ scope_host = context_host >>| Context.build_dir >>= Scope.DB.find_by_dir in
Expander.make_root
~scope
Expand All @@ -282,7 +279,7 @@ let create ~(context : Context.t) ~(host : t option) ~packages ~stanzas =
~public_libs
~artifacts_host
~public_libs_host
and+ artifacts = artifacts in
in
(* Env node that represents the environment configured for the workspace. It
is used as default at the root of every project in the workspace. *)
let default_env =
Expand Down Expand Up @@ -354,7 +351,7 @@ let find_exn name =
let all_init_deferred () =
Memo.Lazy.force all
>>| Context_name.Map.values
>>= Memo.parallel_iter ~f:(fun t -> Artifacts.force t.artifacts)
>>= Memo.parallel_iter ~f:(fun t -> t.artifacts >>= Artifacts.force)
;;

module As_memo_key = struct
Expand Down
5 changes: 3 additions & 2 deletions test/blackbox-tests/test-cases/dynamic-include-stanza/cycle.t
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,8 @@
$ dune build
Error: Dependency cycle between:
dynamic_include a/dune in directory b
-> dynamic_include b/dune in directory a
dynamic_include b/dune in directory a
-> dynamic_include a/dune in directory b
-> dynamic_include b/dune in directory a
-> required by alias default
[1]

0 comments on commit 74bca3f

Please sign in to comment.