stdlib: simplify try_finally signature and implementation

Signed-off-by: Marcello Seri <marcello.seri@gmail.com>
master
Marcello Seri 2018-06-24 11:26:30 +02:00
parent 3f2acd87a3
commit cbb2ed7833
3 changed files with 19 additions and 72 deletions

View File

@ -45,27 +45,13 @@ external _get_raw_backtrace:
external _raise_with_backtrace: exn -> _raw_backtrace -> 'a
= "%raise_with_backtrace"
let try_finally ?(always=fun () -> ()) ?(exceptionally=fun () -> ()) work =
let try_finally ~(always: unit -> unit) work =
match work () with
| result ->
begin match always () with
| () -> result
| exception always_exn ->
let always_bt = _get_raw_backtrace () in
exceptionally ();
_raise_with_backtrace always_exn always_bt
end
| result -> always (); result
| exception work_exn ->
let work_bt = _get_raw_backtrace () in
begin match always () with
| () ->
exceptionally ();
_raise_with_backtrace work_exn work_bt
| exception always_exn ->
let always_bt = _get_raw_backtrace () in
exceptionally ();
_raise_with_backtrace always_exn always_bt
end
let work_bt = _get_raw_backtrace () in
always ();
_raise_with_backtrace work_exn work_bt
(* Composition operators *)

View File

@ -41,27 +41,13 @@ external _get_raw_backtrace:
external _raise_with_backtrace: exn -> _raw_backtrace -> 'a
= "%raise_with_backtrace"
let try_finally ?(always=fun () -> ()) ?(exceptionally=fun () -> ()) work =
let try_finally ~(always: unit -> unit) work =
match work () with
| result ->
begin match always () with
| () -> result
| exception always_exn ->
let always_bt = _get_raw_backtrace () in
exceptionally ();
_raise_with_backtrace always_exn always_bt
end
| result -> always (); result
| exception work_exn ->
let work_bt = _get_raw_backtrace () in
begin match always () with
| () ->
exceptionally ();
_raise_with_backtrace work_exn work_bt
| exception always_exn ->
let always_bt = _get_raw_backtrace () in
exceptionally ();
_raise_with_backtrace always_exn always_bt
end
let work_bt = _get_raw_backtrace () in
always ();
_raise_with_backtrace work_exn work_bt
(* Composition operators *)

View File

@ -51,40 +51,15 @@ exception Exit
(** The [Exit] exception is not raised by any library function. It is
provided for use in your programs. *)
val try_finally :
?always:(unit -> unit) ->
?exceptionally:(unit -> unit) ->
(unit -> 'a) -> 'a
(** [try_finally work ~always ~exceptionally] is designed to run code
in [work] that may fail with an exception, and has two kind of
cleanup routines:
{ul
{- [always], that must be run after {b any} execution
of the function (typically, freeing system resources), and}
{- [exceptionally], that should be run {b only} if [work] or [always]
failed with an exception (typically, undoing user-visible state
changes that would only make sense if the function completes
correctly).}
}
For example:
{[
let outfile = outputprefix ^ ".cmo" in
let oc = open_out_bin objfile in
try_finally
(fun () ->
bytecode
++ Timings.(accumulate_time (Generate sourcefile))
(Emitcode.to_file oc modulename objfile);
Warnings.check_fatal ())
~always:(fun () -> close_out oc)
~exceptionally:(fun _exn -> remove_file objfile);
]}
If [exceptionally] fail with an exception, it is propagated as
usual.
If [always] or [exceptionally] use exceptions internally for
control-flow but do not raise, then [try_finally] is careful to
preserve any exception backtrace coming from [work] or [always]
for easier debugging.
val try_finally : always:(unit -> unit) -> (unit -> 'a) -> 'a
(** [try_finally ~always work] is designed to run code in [work] that
may fail with an exception.
The function [always], is guaranteed to run after {b any} execution
of the [work] function. Exceptions raised by [always] are not
caught, they will be propagated to the caller as usual.
In any other case [try_finally] will return the result of the
[work] funciton or re-raise its exception, preserving the
backtrace (For more details, see {!Printexc.raise_with_backtrace}).
@since NEXT_RELEASE *)