Exceptions
    Fergus Henderson 
    fjh at cs.mu.oz.au
       
    Thu Apr  3 22:00:38 AEST 1997
    
    
  
In mail to mercury at cs.mu.oz.au,
Ralph Becket wrote:
> 
> one thing I haven't been able to find reference to in the Mercury docs is
> exception handling.  Does Mercury have such a facility?  If not, are you
> planning to add one?
Mercury does not have such a facility.  We have in fact spent quite a bit
of time discussing it.  There are still a number of unresolved concerns
regarding the semantics. 
One problem in particular is related to the interaction of exceptions
and destructive update.  This is a problem in other languages with
exceptions and destructive update too, including for example C++.
Exceptions were added to C++ before the consequences were really
understood and the C++ community has still not dealt with the problems;
for example there is still no "exception-safe" implementation of the
C++ Standard Template Library and the C++ committee is in fact still
struggling to specify the semantics of the standard library components
in the presence of exceptions.
Adding exceptions might make it significantly harder to get destructive
update working properly (and that is a difficult enough task already).
I want to wait until we have done that before worrying about exceptions.
That said, exceptions are not very difficult to implement.
That part has been done ;-)
For those who are interested, I have attached the code to do this
below.  The change is very self-contained: I didn't modify any of the
existing files, I just added a new file `exception.m' which
implements the library predicates for throwing and catching exceptions.
So if you want to try this out, you don't need to recompile the Mercury
library or compiler, you can just add `exception.m' to your source code
directory.  However, this code is still experimental and not officially
supported, so please don't rely on it.  Feedback appreciated.
Cheers,
	Fergus.
-- 
Fergus Henderson <fjh at cs.mu.oz.au>   |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>   |  of excellence is a lethal habit"
PGP: finger fjh at 128.250.37.3         |     -- the last words of T. S. Garp.
-----------------------------------------------------------------------------
exception.m:
	New file: adds support for exception handling.
test_exceptions.m:
	New file: some tests of exception handling.
%---------------------------------------------------------------------------%
% Copyright (C) 1997 The University of Melbourne.
% This file may only be copied under the terms of the GNU Library General
% Public License - see the file COPYING.LIB in the Mercury distribution.
%---------------------------------------------------------------------------%
% File: exception.m.
% Main author: fjh.
% Status: not supported!
% This file contains experimental code for exception handling.
% Do not use it.
% XXX this won't work in non-gc grades, because it doesn't have code to
% deep_copy() the thrown exception to the solutions_heap and back;
% instead it just calls fatal_error().
%-----------------------------------------------------------------------------%
%-----------------------------------------------------------------------------%
:- module exception.
:- interface.
:- import_module std_util, io.
%
% throw(Exception):
%	Throw the specified exception.
%
:- pred throw(T).
:- mode throw(in) is erroneous.
%
% try(Goal, Result):
%	Call Goal(R).
%	If Goal(R) fails, fail.
%	If Goal(R) succeeds, succeed with Result = succeeded(R).
%	If Goal(R) throws an exception E, succeed with Result = exception(E).
%
:- type exception_result(T)
	--->	succeeded(T)
	;	exception(univ).
/***************
Sorry, the generic try/2 is not yet implemented.
Currently you must use `try_det', `try_semidet', etc.
:- pred try(pred(T), exception_result(T)).
:- mode try(pred(out) is det,       out) is det.
:- mode try(pred(out) is semidet,   out) is semidet.
:- mode try(pred(out) is cc_multi,  out) is cc_multi.
:- mode try(pred(out) is cc_nondet, out) is cc_nondet.
:- mode try(pred(out) is multi,     out) is multi.
:- mode try(pred(out) is nondet,    out) is nondet.
***************/
:- pred try_det(pred(T), exception_result(T)).
:- mode try_det(pred(out) is det,       out) is det.
:- pred try_semidet(pred(T), exception_result(T)).
:- mode try_semidet(pred(out) is semidet,   out) is semidet.
:- pred try_cc_multi(pred(T), exception_result(T)).
:- mode try_cc_multi(pred(out) is cc_multi,  out) is cc_multi.
:- pred try_cc_nondet(pred(T), exception_result(T)).
:- mode try_cc_nondet(pred(out) is cc_nondet, out) is cc_nondet.
:- pred try_multi(pred(T), exception_result(T)).
:- mode try_multi(pred(out) is multi,     out) is multi.
:- pred try_nondet(pred(T), exception_result(T)).
:- mode try_nondet(pred(out) is nondet,    out) is nondet.
%-----------------------------------------------------------------------------%
%-----------------------------------------------------------------------------%
:- implementation.
throw(T) :-
	type_to_univ(T, Univ),
	builtin_throw(Univ).
/*********************
% This doesn't work, due to 
% 	bash$ mc exception.m
% 	Software error: sorry, not implemented: taking address of pred
% 	`wrap_success/2' with multiple modes.
try(Goal, Result) :-
	builtin_catch(wrap_success(Goal), wrap_exception, Result).
:- pred wrap_success(pred(T), exception_result(T)) is det.
:- mode wrap_success(pred(out) is det, out) is det.
:- mode wrap_success(pred(out) is semidet, out) is semidet.
:- mode wrap_success(pred(out) is cc_multi, out) is cc_multi.
:- mode wrap_success(pred(out) is cc_nondet, out) is cc_nondet.
:- mode wrap_success(pred(out) is multi, out) is multi.
:- mode wrap_success(pred(out) is nondet, out) is nondet.
wrap_success(Goal, succeeded(Result)) :- Goal(Result).
*********************/
try_det(Goal, Result) :-
	builtin_catch(wrap_success_det(Goal), wrap_exception, Result).
try_semidet(Goal, Result) :-
	builtin_catch(wrap_success_semidet(Goal), wrap_exception, Result).
try_cc_multi(Goal, Result) :-
	builtin_catch(wrap_success_cc_multi(Goal), wrap_exception, Result).
try_cc_nondet(Goal, Result) :-
	builtin_catch(wrap_success_cc_nondet(Goal), wrap_exception, Result).
try_multi(Goal, Result) :-
	builtin_catch(wrap_success_multi(Goal), wrap_exception, Result).
try_nondet(Goal, Result) :-
	builtin_catch(wrap_success_nondet(Goal), wrap_exception, Result).
:- pred wrap_success_det(pred(T), exception_result(T)) is det.
:- mode wrap_success_det(pred(out) is det, out) is det.
wrap_success_det(Goal, succeeded(Result)) :- Goal(Result).
:- pred wrap_success_semidet(pred(T), exception_result(T)) is det.
:- mode wrap_success_semidet(pred(out) is semidet, out) is semidet.
wrap_success_semidet(Goal, succeeded(Result)) :- Goal(Result).
:- pred wrap_success_cc_multi(pred(T), exception_result(T)) is det.
:- mode wrap_success_cc_multi(pred(out) is cc_multi, out) is cc_multi.
wrap_success_cc_multi(Goal, succeeded(Result)) :- Goal(Result).
:- pred wrap_success_cc_nondet(pred(T), exception_result(T)) is det.
:- mode wrap_success_cc_nondet(pred(out) is cc_nondet, out) is cc_nondet.
wrap_success_cc_nondet(Goal, succeeded(Result)) :- Goal(Result).
:- pred wrap_success_multi(pred(T), exception_result(T)) is det.
:- mode wrap_success_multi(pred(out) is multi, out) is multi.
wrap_success_multi(Goal, succeeded(Result)) :- Goal(Result).
:- pred wrap_success_nondet(pred(T), exception_result(T)) is det.
:- mode wrap_success_nondet(pred(out) is nondet, out) is nondet.
wrap_success_nondet(Goal, succeeded(Result)) :- Goal(Result).
:- pred wrap_exception(univ::in, exception_result(T)::out) is det.
wrap_exception(Exception, exception(Exception)).
%-----------------------------------------------------------------------------%
:- pred builtin_throw(univ).
:- mode builtin_throw(in) is erroneous.
:- type handler(T) == pred(univ, T).
:- inst handler == (pred(in, out) is det).
:- pred builtin_catch(pred(T), handler(T), T).
:- mode builtin_catch(pred(out) is det,       in(handler), out) is det.
:- mode builtin_catch(pred(out) is semidet,   in(handler), out) is semidet.
:- mode builtin_catch(pred(out) is cc_multi,  in(handler), out) is cc_multi.
:- mode builtin_catch(pred(out) is cc_nondet, in(handler), out) is cc_nondet.
:- mode builtin_catch(pred(out) is multi,     in(handler), out) is multi.
:- mode builtin_catch(pred(out) is nondet,    in(handler), out) is nondet.
% builtin_throw and builtin_catch are implemented below using
% hand-coded low-level C code.
:- external(builtin_throw/1).
:- external(builtin_catch/3).
%-----------------------------------------------------------------------------%
:- pragma c_code("
enum CodeModel { MODEL_DET, MODEL_SEMI, MODEL_NON };
Define_extern_entry(mercury__exception__builtin_catch_3_0); /* det */
Define_extern_entry(mercury__exception__builtin_catch_3_1); /* semidet */
Define_extern_entry(mercury__exception__builtin_catch_3_2); /* cc_multi */
Define_extern_entry(mercury__exception__builtin_catch_3_3); /* cc_nondet */
Define_extern_entry(mercury__exception__builtin_catch_3_4); /* multi */
Define_extern_entry(mercury__exception__builtin_catch_3_6); /* nondet */
Define_extern_entry(mercury__exception__builtin_throw_1_0);
Define_extern_entry(exception_handler_do_fail);
/* the following are defined in runtime/call.mod */
Declare_entry(do_call_det_closure);
Declare_entry(do_call_semidet_closure);
Declare_entry(do_call_nondet_closure);
Declare_label(mercury__exception__builtin_catch_3_2_i1);
Declare_label(mercury__exception__builtin_catch_3_2_i2);
Declare_label(mercury__exception__builtin_catch_3_3_i1);
Declare_label(mercury__exception__builtin_catch_3_3_i2);
Declare_label(mercury__exception__builtin_catch_3_5_i1);
Declare_label(mercury__exception__builtin_catch_3_5_i2);
#ifndef COMPACT_ARGS
Declare_label(mercury__exception__builtin_throw_1_0_i1);
Declare_label(mercury__exception__builtin_throw_1_0_i2);
Declare_label(mercury__exception__builtin_throw_1_0_i3);
#endif
BEGIN_MODULE(exceptions_module)
	init_entry(mercury__exception__builtin_catch_3_0);
	init_entry(mercury__exception__builtin_catch_3_1);
	init_entry(mercury__exception__builtin_catch_3_2);
	init_entry(mercury__exception__builtin_catch_3_3);
	init_entry(mercury__exception__builtin_catch_3_4);
	init_entry(mercury__exception__builtin_catch_3_5);
	init_label(mercury__exception__builtin_catch_3_2_i1);
	init_label(mercury__exception__builtin_catch_3_2_i2);
	init_label(mercury__exception__builtin_catch_3_3_i1);
	init_label(mercury__exception__builtin_catch_3_3_i2);
	init_label(mercury__exception__builtin_catch_3_5_i1);
	init_label(mercury__exception__builtin_catch_3_5_i2);
	init_label(mercury__exception__builtin_throw_1_0);
#ifndef COMPACT_ARGS
	init_label(mercury__exception__builtin_throw_1_0_i1);
	init_label(mercury__exception__builtin_throw_1_0_i2);
	init_label(mercury__exception__builtin_throw_1_0_i3);
#endif
	init_entry(exception_handler_do_fail);
BEGIN_CODE
/*
** builtin_catch(Goal, Handler, Result)
**	call Goal(R).
**	if succeeds, set Result = R.
**	if throws an exception, call Handler(Result).
**
** This is the model_det version.
** On entry, we have a type_info (which we don't use) in r1,
** the Goal to execute in r2 and the Handler in r3.
** On exit, we should put Result in r1 (with COMPACT_ARGS) or r4.
*/
Define_entry(mercury__exception__builtin_catch_3_0); /* det */
Define_entry(mercury__exception__builtin_catch_3_2); /* cc_multi */
	/*
	** Create a handler on the stack with the special redoip
	** of `exception_handler_do_fail' (we'll look for this redoip
	** when unwinding the nondet stack in builtin_throw/1),
	** and save the stuff we will need if an exception is thrown.
	*/
	mkframe(""builtin_catch/3 [model_det]"", 4,
		ENTRY(exception_handler_do_fail));
	framevar(0) = MODEL_DET;
	framevar(1) = r3;		/* save the Handler closure */
	framevar(2) = (Word) sp;	/* save the det stack pointer */
	mark_hp(framevar(3));		/* save the heap pointer (if any) */
	/*
	** Now we need to create another frame.
	** This is so that we can be sure that no-one will hijack
	** the redoip of the special frame we created above.
	** (The compiler sometimes generates ``hijacking'' code that saves
	** the topmost redoip on the stack, and temporarily replaces it
	** with a new redoip that will do some processing on failure
	** before restoring the original redoip.  This would cause
	** problems when doing stack unwinding in builtin_throw/1,
	** because we wouldn't be able to find the special redoip.
	** But code will only ever hijack the topmost frame, so we
	** can avoid this by creating a second frame above the special
	** frame.)
	*/
	succip = LABEL(mercury__exception__builtin_catch_3_2_i1);
	mkframe(""builtin_catch_2/1 [model_det]"", 0, ENTRY(do_fail));
	/*
	** Now call `Goal(Result)'.
	*/
	r1 = r2;	/* The Goal to call */
	r2 = 0;		/* Zero additional input arguments */
	r3 = 1;		/* One output argument */
	call(ENTRY(do_call_det_closure), 
		LABEL(mercury__exception__builtin_catch_3_2_i2),
		LABEL(mercury__exception__builtin_catch_3_2));
		
Define_label(mercury__exception__builtin_catch_3_2_i2);
	update_prof_current_proc(LABEL(mercury__exception__catch_3_2));
	/*
	** On exit from do_call_det_closure, Result is in r1
	*/
#ifndef COMPACT_ARGS
	r4 = r1;
#endif
	succeed_discard();
Define_label(mercury__exception__builtin_catch_3_2_i1);
	succeed_discard();
/*
** builtin_catch(Goal, Handler, Result)
**	call Goal(R).
**	if succeeds, set Result = R.
**	if fails, fail.
**	if throws an exception, call Handler(Result).
**
** This is the model_semi version.
** With COMPACT_ARGS,
** on entry, we have a type_info (which we don't use) in r1,
** the Goal to execute in r2 and the Handler in r3,
** and on exit, we should put Result in r2.
** Without COMPACT_ARGS,
** on entry, we have a type_info (which we don't use) in r2,
** the Goal to execute in r3 and the Handler in r4,
** and on exit, we should put Result in r5.
*/
Define_entry(mercury__exception__builtin_catch_3_1); /* semidet */
Define_entry(mercury__exception__builtin_catch_3_3); /* cc_nondet */
	/*
	** Create a handler on the stack with the special redoip
	** of `exception_handler_do_fail' (we'll look for this redoip
	** when unwinding the nondet stack in builtin_throw/1),
	** and save the stuff we will need if an exception is thrown.
	*/
	mkframe(""builtin_catch/3 [model_semi]"", 4,
		ENTRY(exception_handler_do_fail));
	framevar(0) = MODEL_SEMI;
#ifdef COMPACT_ARGS
	framevar(1) = r3;		/* save the Handler closure */
#else
	framevar(1) = r4;		/* save the Handler closure */
#endif
	framevar(2) = (Word) sp;	/* save the det stack pointer */
	mark_hp(framevar(3));		/* save the heap pointer (if any) */
	/*
	** Now we need to create another frame.
	** This is so that we can be sure that no-one will hijack
	** the redoip of the special frame we created above.
	** (The compiler sometimes generates ``hijacking'' code that saves
	** the topmost redoip on the stack, and temporarily replaces it
	** with a new redoip that will do some processing on failure
	** before restoring the original redoip.  This would cause
	** problems when doing stack unwinding in builtin_throw/1,
	** because we wouldn't be able to find the special redoip.
	** But code will only ever hijacks the topmost frame, so we
	** can avoid this by creating a second frame above the special
	** frame.)
	*/
	succip = LABEL(mercury__exception__builtin_catch_3_3_i1);
	mkframe(""builtin_catch_2/1 [model_semi]"", 0, ENTRY(do_fail));
	/*
	** Now call `Goal(Result)'.
	*/
#ifdef COMPACT_ARGS
	r1 = r2;	/* The Goal to call */
#else
	r1 = r3;	/* The Goal to call */
#endif
	r2 = 0;		/* Zero additional input arguments */
	r3 = 1;		/* One output argument */
	call(ENTRY(do_call_semidet_closure), 
		LABEL(mercury__exception__builtin_catch_3_3_i2),
		LABEL(mercury__exception__builtin_catch_3_3));
		
Define_label(mercury__exception__builtin_catch_3_3_i2);
	update_prof_current_proc(LABEL(mercury__exception__catch_3_3));
	/*
	** On exit from do_call_semidet_closure, the success/failure
	** indicator is in r1, and Result is in r2.
	** Note that we call succeed_discard() to exit regardless
	** of whether r1 is true or false.  We just return the r1 value
	** back to our caller.
	*/
#ifndef COMPACT_ARGS
	r5 = r2;
#endif
	succeed_discard();
Define_label(mercury__exception__builtin_catch_3_3_i1);
	succeed_discard();
/*
** builtin_catch(Goal, Handler, Result)
**	call Goal(R).
**	if succeeds, set Result = R.
**	if fails, fail.
**	if throws an exception, call Handler(Result).
**
** This is the model_non version.
** On entry, we have a type_info (which we don't use) in r1,
** the Goal to execute in r2 and the Handler in r3.
** On exit, we should put Result in r1 (with COMPACT_ARGS) or r3.
*/
Define_entry(mercury__exception__builtin_catch_3_4); /* multi */
Define_entry(mercury__exception__builtin_catch_3_5); /* nondet */
	/*
	** Create a handler on the stack with the special redoip
	** of `exception_handler_do_fail' (we'll look for this redoip
	** when unwinding the nondet stack in builtin_throw/1),
	** and save the stuff we will need if an exception is thrown.
	*/
	mkframe(""builtin_catch/3 [nondet]"", 4,
		ENTRY(exception_handler_do_fail));
	framevar(0) = MODEL_NON;
	framevar(1) = r3;		/* save the Handler closure */
	framevar(2) = (Word) sp;	/* save the det stack pointer */
	mark_hp(framevar(3));		/* save the heap pointer (if any) */
	/*
	** Now we need to create another frame.
	** This is so that we can be sure that no-one will hijack
	** the redoip of the special frame we created above.
	** (The compiler sometimes generates ``hijacking'' code that saves
	** the topmost redoip on the stack, and temporarily replaces it
	** with a new redoip that will do some processing on failure
	** before restoring the original redoip.  This would cause
	** problems when doing stack unwinding in builtin_throw/1,
	** because we wouldn't be able to find the special redoip.
	** But code will only ever hijacks the topmost frame, so we
	** can avoid this by creating a second frame above the special
	** frame.)
	*/
	succip = LABEL(mercury__exception__builtin_catch_3_5_i1);
	mkframe(""builtin_catch_2/1 [nondet]"", 0, ENTRY(do_fail));
	/*
	** Now call `Goal(Result)'.
	*/
	r1 = r2;	/* the Goal to call */
	r2 = 0;		/* Zero additional input arguments */
	r3 = 1;		/* One output argument */
	call(ENTRY(do_call_nondet_closure), 
		LABEL(mercury__exception__builtin_catch_3_5_i2),
		LABEL(mercury__exception__builtin_catch_3_5));
		
Define_label(mercury__exception__builtin_catch_3_5_i2);
	update_prof_current_proc(LABEL(mercury__exception__catch_3_5));
	/*
	** On exit from do_call_nondet_closure, Result is in r1
	*/
#ifndef COMPACT_ARGS
	r3 = r1;
#endif
	succeed();
Define_label(mercury__exception__builtin_catch_3_5_i1);
	succeed();
/*
** builtin_throw(Exception):
**	Throw the specified exception.
**	That means unwinding the nondet stack until we find a handler, and then
**	calling Handler(Result).
**
** On entry, we have Exception in r1.
*/
Define_entry(mercury__exception__builtin_throw_1_0);
{
	Word exception = r1;
	Word handler;
	enum CodeModel catch_code_model;
	/*
	** Search the nondet stack for an exception handler,
	** i.e. a frame whose redoip is `exception_handler_do_fail'
	** (one created by `builtin_catch').
	** N.B.  We search down the `succfr' chain, not the `prevfr' chain;
	** this ensures that we only find handlers installed by our callers,
	** not handlers installed by procedures that we called but which
	** are still on the nondet stack because they choice points behind.
	*/
	do {
		curfr = cursuccfr;
		if (curfr < nondetstack_zone->min) {
			fatal_error(""builtin_throw/1: uncaught exception"");
		}
	} while (curredoip != ENTRY(exception_handler_do_fail));
	/*
	** Save the handler we found, reset the det stack to and heap,
	** pop the final exception handler frame off the nondet stack,
	** and reset the nondet stack top.
	*/
	succip = cursuccip;
	catch_code_model = framevar(0);
	handler = framevar(1);	
	sp = (Word) framevar(2);	/* reset the det stack pointer */
	restore_hp(framevar(3));	/* reset the heap pointer (if any) */
	maxfr = curprevfr;
	curfr = maxfr;
#ifndef CONSERVATIVE_GC
	/* XXX we need to do deep_copy() on the exception object */
	fatal_error(""throw/1 not implemented for non-gc grades"");
#endif
	/*
	** Now invoke the handler that we found, as `Handler(Result)',
	*/
	r1 = handler;		/* get the Handler closure */
	r2 = 1;			/* One additional input argument */
	r3 = 1;			/* One output argument */
	r4 = exception;		/* This is our one input argument */
#ifdef COMPACT_ARGS
	/*
	** If the catch was semidet, we need to set the success indicator
	** r1 to TRUE and return the result in r2; otherwise, we return
	** the result in r1, which is where do_call_det_closure puts it,
	** so we can to a tailcall.
	*/
	if (catch_code_model != MODEL_SEMI) {
		tailcall(ENTRY(do_call_det_closure), 
			LABEL(mercury__exception__builtin_throw_1_0));
	}
	push(succip);
	call(ENTRY(do_call_det_closure), 
		LABEL(mercury__exception__builtin_throw_1_0_i1),
		LABEL(mercury__exception__builtin_throw_1_0));
}
Define_label(mercury__exception__builtin_throw_1_0_i1);
	r2 = r1;
	r1 = TRUE;
	succip = (Code *) pop();
	proceed();
#else /* not COMPACT_ARGS */
	push(succip);
	push(catch_code_model);
	call(ENTRY(do_call_det_closure), 
		LABEL(mercury__exception__builtin_throw_1_0_i1)),
		LABEL(mercury__exception__builtin_throw_1_0));
}
Define_label(mercury__exception__builtin_throw_1_0_i1);
	/* we've just returned from do_call_det_closure */
	catch_code_model = pop();
	if (catch_code_model == MODEL_SEMI) {
		r5 = r1;
	else {
		r4 = r1;
	}
	succip = (Code *) pop();
	proceed();
#endif /* not COMPACT_ARGS */
Define_entry(exception_handler_do_fail);
	/*
	** `exception_handler_do_fail' is the same as `do_fail':
	** it just invokes fail().  The reason we don't just use
	** `do_fail' for this is that when unwinding the stack we
	** check for a redoip of `exception_handler_do_fail' and
	** handle it specially.
	*/
	fail();
END_MODULE
/* suppress gcc -Wmissing-decls warning */
void mercury_sys_init_exceptions(void);
void mercury_sys_init_exceptions(void) {
	exceptions_module();
}
").
%-----------------------------------------------------------------------------%
%-----------------------------------------------------------------------------%
% Copyright (C) 1997 The University of Melbourne.
% This file may only be copied under the terms of the GNU General
% Public License - see the file COPYING in the Mercury distribution.
%-----------------------------------------------------------------------------%
% File: test_exceptions.m.
% Main author: fjh.
% Test cases for exception handling.
% XXX we should test nested exception handlers.
%-----------------------------------------------------------------------------%
:- module test_exceptions.
:- interface.
:- import_module io.
:- pred main(io__state::di, io__state::uo) is cc_multi.
:- implementation.
:- import_module std_util.
:- import_module exception.
main --> 
	{ try_det(det_throw, DetThrowResult) },
	write("det_throw: "), write(DetThrowResult), nl,
	{ try_det(det_succeed, DetSucceedResult) },
	write("det_succeed: "), write(DetSucceedResult), nl,
	(if { try_semidet(semidet_throw, SemidetThrowResult) } then
		write("semidet_throw: "), write(SemidetThrowResult), nl
	else
		write("semidet_throw failed"), nl
	),
	(if { try_semidet(semidet_succeed, SemidetSucceedResult) } then
		write("semidet_succeed: "), write(SemidetSucceedResult), nl
	else
		write("semidet_succeed failed"), nl
	),
	(if { try_semidet(semidet_fail, SemidetFailResult) } then
		write("semidet_fail: "), write(SemidetFailResult), nl
	else
		write("semidet_fail failed"), nl
	),
	{ try_cc_multi(cc_multi_throw, CCMultiThrowResult) },
	write("cc_multi_throw: "), write(CCMultiThrowResult), nl,
	{ try_cc_multi(cc_multi_succeed, CCMultiSucceedResult) },
	write("cc_multi_succeed: "), write(CCMultiSucceedResult), nl,
	(if { try_cc_nondet(cc_nondet_throw, CCNondetThrowResult) } then
		write("cc_nondet_throw: "), write(CCNondetThrowResult), nl
	else
		write("cc_nondet_throw failed"), nl
	),
	(if { try_cc_nondet(cc_nondet_succeed, CCNondetSucceedResult) } then
		write("cc_nondet_succeed: "), write(CCNondetSucceedResult), nl
	else
		write("cc_nondet_succeed failed"), nl
	),
	(if { try_cc_nondet(cc_nondet_fail, CCNondetFailResult) } then
		write("cc_nondet_fail: "), write(CCNondetFailResult), nl
	else
		write("cc_nondet_fail failed"), nl
	),
	{ solutions(try_multi(multi_throw), MultiThrowResult) },
	write("multi_throw: "), write(MultiThrowResult), nl,
	{ solutions(try_multi(multi_succeed), MultiSucceedResult) },
	write("multi_succeed: "), write(MultiSucceedResult), nl,
	{ solutions(try_multi(multi_succeed_then_throw),
		MultiSucceedThenThrowResult) },
	write("multi_succeed_then_throw: "),
	write(MultiSucceedThenThrowResult), nl,
	{ solutions(try_nondet(nondet_throw), NondetThrowResult) },
	write("nondet_throw: "), write(NondetThrowResult), nl,
	{ solutions(try_nondet(nondet_succeed), NondetSucceedResult) },
	write("nondet_succeed: "), write(NondetSucceedResult), nl,
	{ solutions(try_nondet(nondet_fail), NondetFailResult) },
	write("nondet_fail: "), write(NondetFailResult), nl,
	{ solutions(try_nondet(nondet_succeed_then_throw),
		NondetSucceedThenThrowResult) },
	write("nondet_succeed_then_throw: "),
	write(NondetSucceedThenThrowResult), nl.
:- pred det_throw(string::out) is det.
det_throw(_) :- throw("det_throw").
:- pred semidet_throw(string::out) is semidet.
semidet_throw(_) :- throw("semidet_throw").
:- pred nondet_throw(string::out) is nondet.
nondet_throw(_) :- throw("nondet_throw").
:- pred multi_throw(string::out) is multi.
multi_throw(_) :- throw("multi_throw").
:- pred cc_nondet_throw(string::out) is cc_nondet.
cc_nondet_throw(_) :- throw("cc_nondet_throw").
:- pred cc_multi_throw(string::out) is cc_multi.
cc_multi_throw(_) :- throw("cc_multi_throw").
:- pred det_succeed(string::out) is det.
det_succeed("det_succeed").
:- pred semidet_succeed(string::out) is semidet.
semidet_succeed("semidet_succeed").
:- pred nondet_succeed(string::out) is nondet.
nondet_succeed("nondet_succeed 1").
nondet_succeed("nondet_succeed 2").
:- pred multi_succeed(string::out) is multi.
multi_succeed("multi_succeed 1").
multi_succeed("multi_succeed 2").
:- pred cc_nondet_succeed(string::out) is cc_nondet.
cc_nondet_succeed("cc_nondet_succeed").
cc_nondet_succeed("cc_nondet_succeed 2").
:- pred cc_multi_succeed(string::out) is cc_multi.
cc_multi_succeed("cc_multi_succeed").
cc_multi_succeed("cc_multi_succeed 2").
:- pred semidet_fail(string::out) is semidet.
semidet_fail("semidet_fail") :- fail.
:- pred nondet_fail(string::out) is nondet.
nondet_fail("nondet_fail 1") :- fail.
nondet_fail("nondet_fail 2") :- fail.
:- pred cc_nondet_fail(string::out) is cc_nondet.
cc_nondet_fail("cc_nondet_fail") :- fail.
cc_nondet_fail("cc_nondet_succeed 2") :- fail.
:- pred nondet_succeed_then_throw(string::out) is nondet.
nondet_succeed_then_throw("nondet_succeed_then_throw 1").
nondet_succeed_then_throw("nondet_succeed_then_throw 2").
nondet_succeed_then_throw(_) :- throw("nondet_succeed_then_throw 3").
nondet_succeed_then_throw("nondet_succeed_then_throw 4").
:- pred multi_succeed_then_throw(string::out) is multi.
multi_succeed_then_throw("multi_succeed_then_throw 1").
multi_succeed_then_throw("multi_succeed_then_throw 2").
multi_succeed_then_throw(_) :- throw("multi_succeed_then_throw 3").
multi_succeed_then_throw("multi_succeed_then_throw 4").
%-----------------------------------------------------------------------------%
    
    
More information about the users
mailing list