@@ -36,6 +36,9 @@ module T = struct
36
36
| Goal : 'a t -> 'a t
37
37
| Action : Action_desc .t t -> unit t
38
38
| 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
39
42
40
43
and 'a memo =
41
44
{ name : string
@@ -78,6 +81,9 @@ let ignore x = Map (Fun.const (), x)
78
81
79
82
let map2 x y ~f = Map2 (f, x, y)
80
83
84
+ let push_stack_frame ~human_readable_description f =
85
+ Push_stack_frame (human_readable_description, f)
86
+
81
87
let delayed f = Map (f, Pure () )
82
88
83
89
let all_unit xs =
@@ -408,134 +414,20 @@ struct
408
414
let * act, facts = exec t in
409
415
let + s = Build_deps. execute_action_stdout ~observing_facts: facts act in
410
416
(s, Dep.Map. empty)
417
+ | Push_stack_frame (human_readable_description , f ) ->
418
+ Memo. push_stack_frame ~human_readable_description (fun () ->
419
+ exec (f () ))
411
420
end
412
421
413
422
include Execution
414
423
end
415
424
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
-
535
425
let dyn_memo_build_deps t = dyn_deps (dyn_memo_build t)
536
426
537
427
let dep_on_alias_if_exists t = Dep_on_alias_if_exists t
538
428
539
429
module List = struct
540
430
let map l ~f = all (List. map l ~f )
431
+
432
+ let concat_map l ~f = map l ~f >> | List. concat
541
433
end
0 commit comments