[mercury-users] Can not make "mode" while rewriting Prolog -> Mercury

Fergus Henderson fjh at cs.mu.OZ.AU
Fri Nov 1 05:18:19 AEDT 2002


On 31-Oct-2002, Mike Potanin <potanin at mccme.ru> wrote:
> 
> For test "declarative message passing" I write simple programm on Curry
> and Prolog. This programms run 3 "parallel" stack-based
> message-controlling calculators.
> Curry version http://wtk.ru/pm/fp/st.curry
> Prolog version http://wtk.ru/pm/fp/st.pl
> I want write Mercury version. I modify Prolog program
> (http://wtk.ru/pm/fp/st.m), but it do not compile.
> I can not make right mode for message queue.
> Help me, please.

I think this example requires dynamic modes (the `any' inst)
and dynamic scheduling, which in Mercury means means making use of
extras/trailed_update/var.m from the mercury-extras distribution.
See the code below.  It compiles with no errors or warnings,
and outputs "17", which hopefully is the correct answer.

One suggestion: try not to squeeze so many things on a single line.
The Mercury compiler's error messages only specify the line number,
not the column number, so you'll find it easier to understand them if
you don't put so many things on a single line.

:- module st.
:- interface.
:- import_module io.

:- pred main(io__state::di, io__state::uo) is cc_multi.

:- implementation.
:- import_module list, char, int, string, std_util.
:- import_module var.

:- type op ---> plus.

:- pred calc(int, op, int, int).
:- mode calc(in, in, in, out) is det.
calc(X, plus, Y, Z) :- Z is X + Y.

:- inst listskel(Inst) == bound( [] ; [Inst | listskel(Inst)] ).

:- type msg ---> send(int,int,var(int)); op2to1(int,op).
:- inst msgskel == bound( send(ground,ground,any) ; op2to1(ground,ground) ). 
:- mode msq == listskel(msgskel) >> listskel(msgskel).

:- pred st(int, list(msg), list(var(int))).
:- mode st(in, msq, in(list_skel(any))) is semidet.

st(_,[],_).
st(N,[Msg|C], S) :-
	( op2to1(A,O) = Msg,
		( A = N ->
			S = [X,Y|T],
			freeze_var(X,(pred(XV::in, Z2::in(any)) is semidet :-
				freeze(Y,(pred(YV::in, Z1::out) is det :-
					calc(XV,O,YV,Z1)), Z2)), Z),
			st(N, C, [Z|T])
		;
			st(N, C, S)
		)
	; send(A,B,V) = Msg,
		( A = N ->
			[V|T] = S,
			st(N, C, T)
		; B = N ->
			st(N, C, [V|S])
		;
			st(N, C, S)
		)
	).

:- pred test(list(msg)).
:- mode test(msq) is semidet.

test(C) :- st(1,C,[]), st(2,C,[]).

:- pred runtest(var(int)).
:- mode runtest(out(any)) is semidet.

runtest(Y) :-   init(X), init(U), init(Y),
		test([send(0,1,var(5)),
		    send(0,2,X),
		    send(0,1,var(12)),
		    send(1,0,X),
		    send(1,2,U),
		    op2to1(2,plus),
		    send(2,0,Y)]).

main -->
	( { runtest(Y) } ->
		{ var__is_ground(Y,YR) },
		( { YR = yes(R) } ->
			io__print(R)
		;
			io__print("unbound")
		)
	;
		io__print("failed")
	),
	io__nl.

-- 
Fergus Henderson <fjh at cs.mu.oz.au>  |  "I have always known that the pursuit
The University of Melbourne         |  of excellence is a lethal habit"
WWW: <http://www.cs.mu.oz.au/~fjh>  |     -- the last words of T. S. Garp.
--------------------------------------------------------------------------
mercury-users mailing list
post:  mercury-users at cs.mu.oz.au
administrative address: owner-mercury-users at cs.mu.oz.au
unsubscribe: Address: mercury-users-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-users-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the users mailing list