Skip to content

Commit

Permalink
No longer generate approximate merlin files (#4607)
Browse files Browse the repository at this point in the history
And by doing so remove the last exception handling function from
Memo.Build.

Signed-off-by: Jeremie Dimino <[email protected]>
  • Loading branch information
jeremiedimino authored May 13, 2021
1 parent 6e25cdd commit edbc94c
Show file tree
Hide file tree
Showing 6 changed files with 6 additions and 26 deletions.
5 changes: 5 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,11 @@ Unreleased
- Remove `dune compute`. It was broken and unused (#4540,
@jeremiedimino)

- No longer generate an approximate merlin files when computing the
ocaml flags fails, for instance because they include the contents of
a file that failed to build. This was a niche feature and it was
getting in the way of making Dune's core better. (#4607, @jeremiedimino)

2.9.0 (unreleased)
------------------

Expand Down
11 changes: 0 additions & 11 deletions src/dune_engine/action_builder.ml
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ module T = struct
| Dyn_deps : ('a * Dep.Set.t) t -> 'a t
| Fail : fail -> _ t
| Memo : 'a memo -> 'a t
| Catch : 'a t * 'a -> 'a t
| Deps : Dep.Set.t -> unit t
| Memo_build : 'a Memo.Build.t -> 'a t
| Dyn_memo_build : 'a Memo.Build.t t -> 'a t
Expand Down Expand Up @@ -122,8 +121,6 @@ let env_var s = Deps (Dep.Set.singleton (Dep.env s))

let alias a = dep (Dep.alias a)

let catch t ~on_error = Catch (t, on_error)

let contents p = Contents p

let lines_of p = Lines_of p
Expand Down Expand Up @@ -380,10 +377,6 @@ struct
Build_deps.file_exists p >>= function
| true -> exec then_
| false -> exec else_)
| Catch (t, on_error) -> (
Memo.Build.swallow_errors (fun () -> exec t) >>| function
| Ok r -> r
| Error () -> (on_error, Dep.Map.empty))
| Memo m -> Memo_poly.eval m
| Memo_build f ->
let+ f = f in
Expand Down Expand Up @@ -450,7 +443,6 @@ let rec can_eval_statically : type a. a t -> bool = function
| Fail _ -> true
| If_file_exists (_, _, _) -> false
| Memo _ -> false
| Catch (t, _) -> can_eval_statically t
| Memo_build _ -> false
| Dyn_memo_build _ -> false
| Bind _ ->
Expand Down Expand Up @@ -518,9 +510,6 @@ let static_eval =
| Fail { fail } -> fail ()
| If_file_exists (_, _, _) -> assert false
| Memo _ -> assert false
| Catch (t, v) -> (
try loop t acc with
| _ -> (v, Dep.Set.empty))
| Memo_build _ -> assert false
| Dyn_memo_build _ -> assert false
| Bind _ -> assert false
Expand Down
4 changes: 0 additions & 4 deletions src/dune_engine/action_builder.mli
Original file line number Diff line number Diff line change
Expand Up @@ -154,10 +154,6 @@ val dyn_path_set : ('a * Path.Set.t) t -> 'a t

val dyn_path_set_reuse : Path.Set.t t -> Path.Set.t t

(** [catch t ~on_error] evaluates to [on_error] if an exception is raised during
the evaluation of [t]. *)
val catch : 'a t -> on_error:'a -> 'a t

(** [contents path] returns a description that when run will return the contents
of the file at [path]. *)
val contents : Path.t -> string t
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -246,7 +246,7 @@ module Unprocessed = struct
let config =
{ stdlib_dir
; requires
; flags = Action_builder.catch flags ~on_error:[]
; flags
; preprocess
; libname
; source_dirs
Expand Down
6 changes: 0 additions & 6 deletions src/memo/memo.ml
Original file line number Diff line number Diff line change
Expand Up @@ -53,12 +53,6 @@ module Build0 = struct

let of_reproducible_fiber = Fun.id

let swallow_errors f =
Fiber.map_reduce_errors
(module Monoid.Unit)
f
~on_error:(fun _ -> Fiber.return ())

module Option = struct
let iter option ~f =
match option with
Expand Down
4 changes: 0 additions & 4 deletions src/memo/memo.mli
Original file line number Diff line number Diff line change
Expand Up @@ -77,10 +77,6 @@ module Build : sig
end
[@@inline always]

(** [swallow_errors f] swallows any error raised during the execution of [f].
Use this function if you are ok with a computation failing. *)
val swallow_errors : (unit -> 'a t) -> ('a, unit) Result.t t

module Option : sig
val iter : 'a option -> f:('a -> unit t) -> unit t

Expand Down

0 comments on commit edbc94c

Please sign in to comment.