Skip to content

Commit ef05a2e

Browse files
Get rid of the last remaning bits of "static evaluation" (#4662)
Signed-off-by: Jeremie Dimino <jeremie@dimino.org>
1 parent 0501664 commit ef05a2e

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

41 files changed

+1107
-1021
lines changed

src/dune_engine/action_builder.ml

+11-119
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,9 @@ module T = struct
3636
| Goal : 'a t -> 'a t
3737
| Action : Action_desc.t t -> unit t
3838
| Action_stdout : Action_desc.t t -> string t
39+
| Push_stack_frame :
40+
(unit -> User_message.Style.t Pp.t) * (unit -> 'a t)
41+
-> 'a t
3942

4043
and 'a memo =
4144
{ name : string
@@ -78,6 +81,9 @@ let ignore x = Map (Fun.const (), x)
7881

7982
let map2 x y ~f = Map2 (f, x, y)
8083

84+
let push_stack_frame ~human_readable_description f =
85+
Push_stack_frame (human_readable_description, f)
86+
8187
let delayed f = Map (f, Pure ())
8288

8389
let all_unit xs =
@@ -408,134 +414,20 @@ struct
408414
let* act, facts = exec t in
409415
let+ s = Build_deps.execute_action_stdout ~observing_facts:facts act in
410416
(s, Dep.Map.empty)
417+
| Push_stack_frame (human_readable_description, f) ->
418+
Memo.push_stack_frame ~human_readable_description (fun () ->
419+
exec (f ()))
411420
end
412421

413422
include Execution
414423
end
415424

416-
(* Static evaluation *)
417-
418-
(* Note: there is some duplicated logic between [can_eval_statically] and
419-
[static_eval]. More precisely, [can_eval_statically] returns [false] exactly
420-
for the nodes [static_eval] produces [assert false]. The duplication is not
421-
ideal, but the code is simpler this way and also we expect that we will get
422-
rid of this function eventually, once we have pushed the [Memo.Build.t] monad
423-
enough in the code base.
424-
425-
If this code ends being more permanent that we expected, we should probably
426-
get rid of the duplication. This code was introduced on February 2021, to
427-
give an idea of how long it has been here. *)
428-
429-
let rec can_eval_statically : type a. a t -> bool = function
430-
| Pure _ -> true
431-
| Map (_, a) -> can_eval_statically a
432-
| Both (a, b) -> can_eval_statically a && can_eval_statically b
433-
| Seq (a, b) -> can_eval_statically a && can_eval_statically b
434-
| Map2 (_, a, b) -> can_eval_statically a && can_eval_statically b
435-
| All xs -> List.for_all xs ~f:can_eval_statically
436-
| Paths_glob _ -> false
437-
| Deps _ -> true
438-
| Dyn_paths b -> can_eval_statically b
439-
| Dyn_deps b -> can_eval_statically b
440-
| Source_tree _ -> false
441-
| Contents _ -> false
442-
| Lines_of _ -> false
443-
| Fail _ -> true
444-
| If_file_exists (_, _, _) -> false
445-
| Memo _ -> false
446-
| Memo_build _ -> false
447-
| Dyn_memo_build _ -> false
448-
| Bind _ ->
449-
(* TODO jeremiedimino: This should be [can_eval_statically t], however it
450-
breaks the [Expander.set_artifacts_dynamic] trick that it used to break a
451-
cycle. The cycle is as follow:
452-
453-
- [(rule (deps %{cmo:x}) ..)] requires expanding %{cmo:x}
454-
455-
- expanding %{cmo:x} requires computing the artifacts DB
456-
457-
- computing the artifacts DB requires computing the module<->library
458-
assignment
459-
460-
- computing the above requires knowing the set of source files (static
461-
and generated) in a given directory
462-
463-
- computing the above works by looking at the source tree and adding all
464-
targets of user rules
465-
466-
- computing targets of user rules is done by effectively generating the
467-
rules for the user rules, which means interpreting the [(deps
468-
%{cmo:...})] thing
469-
470-
If we find another way to break this cycle we should be able to change
471-
this code. *)
472-
false
473-
| Dep_on_alias_if_exists _ -> false
474-
| Goal t -> can_eval_statically t
475-
| Action _ -> false
476-
| Action_stdout _ -> false
477-
478-
let static_eval =
479-
let rec loop : type a. a t -> Dep.Set.t -> a * Dep.Set.t =
480-
fun t acc ->
481-
match t with
482-
| Pure x -> (x, acc)
483-
| Map (f, a) ->
484-
let x, acc = loop a acc in
485-
(f x, acc)
486-
| Both (a, b) ->
487-
let a, acc = loop a acc in
488-
let b, acc = loop b acc in
489-
((a, b), acc)
490-
| Seq (a, b) ->
491-
let (), acc = loop a acc in
492-
let b, acc = loop b acc in
493-
(b, acc)
494-
| Map2 (f, a, b) ->
495-
let a, acc = loop a acc in
496-
let b, acc = loop b acc in
497-
(f a b, acc)
498-
| All xs -> loop_many [] xs acc
499-
| Paths_glob _ -> assert false
500-
| Deps deps -> ((), Dep.Set.union deps acc)
501-
| Dyn_paths b ->
502-
let (x, ps), acc = loop b acc in
503-
(x, Dep.Set.union (Dep.Set.of_files_set ps) acc)
504-
| Dyn_deps b ->
505-
let (x, deps), acc = loop b acc in
506-
(x, Dep.Set.union deps acc)
507-
| Source_tree _ -> assert false
508-
| Contents _ -> assert false
509-
| Lines_of _ -> assert false
510-
| Fail { fail } -> fail ()
511-
| If_file_exists (_, _, _) -> assert false
512-
| Memo _ -> assert false
513-
| Memo_build _ -> assert false
514-
| Dyn_memo_build _ -> assert false
515-
| Bind _ -> assert false
516-
| Dep_on_alias_if_exists _ -> assert false
517-
| Goal t -> loop t acc
518-
| Action _ -> assert false
519-
| Action_stdout _ -> assert false
520-
and loop_many : type a. a list -> a t list -> Dep.Set.t -> a list * Dep.Set.t
521-
=
522-
fun acc_res l acc ->
523-
match l with
524-
| [] -> (List.rev acc_res, acc)
525-
| t :: l ->
526-
let x, acc = loop t acc in
527-
loop_many (x :: acc_res) l acc
528-
in
529-
fun t ->
530-
if can_eval_statically t then
531-
Some (loop t Dep.Set.empty)
532-
else
533-
None
534-
535425
let dyn_memo_build_deps t = dyn_deps (dyn_memo_build t)
536426

537427
let dep_on_alias_if_exists t = Dep_on_alias_if_exists t
538428

539429
module List = struct
540430
let map l ~f = all (List.map l ~f)
431+
432+
let concat_map l ~f = map l ~f >>| List.concat
541433
end

src/dune_engine/action_builder.mli

+7-5
Original file line numberDiff line numberDiff line change
@@ -86,8 +86,15 @@ val all_unit : unit t list -> unit t
8686

8787
module List : sig
8888
val map : 'a list -> f:('a -> 'b t) -> 'b list t
89+
90+
val concat_map : 'a list -> f:('a -> 'b list t) -> 'b list t
8991
end
9092

93+
val push_stack_frame :
94+
human_readable_description:(unit -> User_message.Style.t Pp.t)
95+
-> (unit -> 'a t)
96+
-> 'a t
97+
9198
(** Delay a static computation until the description is evaluated *)
9299
val delayed : (unit -> 'a) -> 'a t
93100

@@ -253,11 +260,6 @@ val action : Action_desc.t t -> unit t
253260
(** Same as [action], but captures the output of the action. *)
254261
val action_stdout : Action_desc.t t -> string t
255262

256-
(** {1 Analysis} *)
257-
258-
(** Returns [Some (x, deps)] if the following can be evaluated statically. *)
259-
val static_eval : 'a t -> ('a * Dep.Set.t) option
260-
261263
(** [goal t] ignores all facts that have been accumulated about the dependencies
262264
of [t]. For example, [goal (path p)] declares that a path [p] contributes to
263265
the "goal" of the resulting action builder, which means [p] must be built,

src/dune_engine/string_with_vars.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -296,7 +296,7 @@ struct
296296
{ t with parts }
297297
end
298298

299-
include Make_expander (Applicative.Id)
299+
include Make_expander (Memo.Build)
300300

301301
let is_pform t pform =
302302
match t.parts with

src/dune_engine/string_with_vars.mli

+1-1
Original file line numberDiff line numberDiff line change
@@ -119,7 +119,7 @@ module type Expander = sig
119119
t -> dir:Path.t -> f:Value.t list option app expander -> t app
120120
end
121121

122-
include Expander with type 'a app := 'a
122+
include Expander with type 'a app := 'a Memo.Build.t
123123

124124
module Make_expander (A : Applicative) : Expander with type 'a app := 'a A.t
125125

src/dune_lang/template.mli

+2
Original file line numberDiff line numberDiff line change
@@ -7,6 +7,8 @@ module Pform : sig
77
; payload : string option
88
}
99

10+
val to_string : t -> string
11+
1012
val to_dyn : t -> Dyn.t
1113

1214
val name : t -> string

0 commit comments

Comments
 (0)