Skip to content

Commit

Permalink
Misc.protect_refs: use Fun.protect to protect the backtrace
Browse files Browse the repository at this point in the history
Currently Fun.protect and Misc.try_finally can be used in code that
tries carefully to preserve the first-failure backtrace, but
Misc.protect_refs cannot. This PR fixes the discrepancy. See ocaml#9057 for
a use-case.

See the GPR ( ocaml#9060 ) for an
in-depth discussion of the potential performance impact of this
change.
  • Loading branch information
gasche committed Nov 7, 2019
1 parent 65e6874 commit f5252e9
Show file tree
Hide file tree
Showing 3 changed files with 6 additions and 4 deletions.
3 changes: 3 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -43,6 +43,9 @@ Working version
(matching on the effects of a copmutation) in the typedtree.
(Gabriel Scherer, review by Jacques Garrigue and Alain Frisch)

- #9060: ensure that Misc.protect_refs preserves backtraces
(Gabriel Scherer, review by Guillaume Munch-Maccagnoni and David Allsopp)

- #9078: make all compilerlibs/ available to ocamltest.
(Gabriel Scherer, review by Sébastien Hinderer)

Expand Down
4 changes: 1 addition & 3 deletions utils/misc.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,9 +56,7 @@ let protect_refs =
fun refs f ->
let backup = List.map (fun (R (r, _)) -> R (r, !r)) refs in
set_refs refs;
match f () with
| x -> set_refs backup; x
| exception e -> set_refs backup; raise e
Fun.protect ~finally:(fun () -> set_refs backup) f

(* List functions *)

Expand Down
3 changes: 2 additions & 1 deletion utils/misc.mli
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,8 @@ type ref_and_value = R : 'a ref * 'a -> ref_and_value
val protect_refs : ref_and_value list -> (unit -> 'a) -> 'a
(** [protect_refs l f] temporarily sets [r] to [v] for each [R (r, v)] in [l]
while executing [f]. The previous contents of the references is restored
even if [f] raises an exception. *)
even if [f] raises an exception, without altering the exception backtrace.
*)

module Stdlib : sig
module List : sig
Expand Down

0 comments on commit f5252e9

Please sign in to comment.