[m-rev.] for review: moose fixes

Julien Fischer juliensf at students.cs.mu.OZ.AU
Thu Jul 24 14:38:02 AEST 2003


On Wed, 23 Jul 2003, Fergus Henderson wrote:

> On 23-Jul-2003, Julien Fischer <juliensf at students.cs.mu.OZ.AU> wrote:
> > On Wed, 23 Jul 2003, Fergus Henderson wrote:
> > > 	- Don't you need to also modify term_to_ite
> > > 	  (in extras/moose/mercury_syntax.m) to handle the
> > > 	  new kind of it-then-else goals?
> >
> > On closer inspection term_to_ite and a number of other predicates
> > aren't actually used.  Moose compiles and runs quite happily without
> > them.  Are they just dead code or was there some (unimplemented) purpose
> > to them?
>
> No idea.  Feel free to delete them.
>
Done.

I've also altered one of the .moo files in the samples directory to
use the alternative if-then-else notation.

An amended log message and diff follows (interdiff refused to have
to have anything to do with it for some reason).


Estimated hours taken: 1.
Branches: main.

Allow moose to parse conditional goals written using the if - then - else
notation.  This makes the code generated by moose less ugly when the `.moo'
file contains these type of goals.

extras/moose/mercury_syntax.m:
	Handle if-then-elses so that the generated code is less ugly.
	Fix some indentation.
	Fix some type declarations.
	Delete some dead code.

extras/moose/check.m:
extras/moose/grammar.m:
	Add some module qualifiers.

extras/moose/samples/alpha.moo:
	Use the alternative if-then-else notation.


Index: check.m
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/moose/check.m,v
retrieving revision 1.3
diff -u -r1.3 check.m
--- check.m	16 Jul 2003 07:16:02 -0000	1.3
+++ check.m	22 Jul 2003 08:44:29 -0000
@@ -55,7 +55,7 @@
 %------------------------------------------------------------------------------%

 check_rule_decls(DeclList, Decls, Errors) :-
-	init(Decls0),
+	map__init(Decls0),
 	check_rule_decls(DeclList, Decls0, Decls, Errors).

 :- pred check_rule_decls(list(rule_decl), rule_decls, rule_decls,
@@ -85,7 +85,7 @@
 %------------------------------------------------------------------------------%

 check_clauses(ClauseList, Decls, Clauses, Errors) :-
-	init(Clauses0),
+	map__init(Clauses0),
 	check_clauses0(ClauseList, Decls, Clauses0, Clauses, Errors0),

 	map__keys(Decls, DeclIds),
Index: grammar.m
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/moose/grammar.m,v
retrieving revision 1.7
diff -u -r1.7 grammar.m
--- grammar.m	16 Jul 2003 07:16:03 -0000	1.7
+++ grammar.m	22 Jul 2003 08:43:40 -0000
@@ -233,8 +233,8 @@
 		% Keep the nonterminals in reverse sorted order
 		% for efficient processing in lalr.m
 	map__map_values((pred(_K::in, V0::in, V::out) is det :-
-	    sort(V0, V1),
-	    reverse(V1, V)
+	    list__sort(V0, V1),
+	    list__reverse(V1, V)
 	), ClauseIndex3, ClauseIndex4),
 	Grammar = grammar(Rules3, AllClauses3, XForms3, Nont3, ClauseIndex4,
 		First3, Follow3).
Index: mercury_syntax.m
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/moose/mercury_syntax.m,v
retrieving revision 1.2
diff -u -r1.2 mercury_syntax.m
--- mercury_syntax.m	16 Jul 2003 07:16:02 -0000	1.2
+++ mercury_syntax.m	22 Jul 2003 21:05:06 -0000
@@ -39,8 +39,7 @@

 :- type lines
 	--->	lines
-	;	nolines
-	.
+	;	nolines.

 :- pred write_element(lines, element, io__state, io__state).
 :- mode write_element(in, in, di, uo) is det.
@@ -51,8 +50,7 @@
 :- type (type)
 	--->	abstr(term)
 	;	equiv(term, term)
-	;	disj(term, list(term))
-	.
+	;	disj(term, list(term)).

 :- pred term_to_type(term, (type)).
 :- mode term_to_type(in, out) is semidet.
@@ -68,8 +66,7 @@
 	;	forall(vars, goal)
 	% 	(goal => goal) % XXX conflicts with type classes
 	;	(goal <= goal)
-	;	(goal <=> goal)
-	.
+	;	(goal <=> goal).

 :- pred term_to_goal(term, goal).
 :- mode term_to_goal(in, out) is semidet.
@@ -264,34 +261,6 @@
 	--->	normal
 	;	dcg.

-:- pred write_goal_term(lines, int, goal_type, term, varset,
-		io__state, io__state).
-:- mode write_goal_term(in, in, in, in, in, di, uo) is det.
-
-write_goal_term(Lines, Ind, Type, Term, VarSet, !IO) :-
-	( term_to_conj(Term, Conjuncts) ->
-		write_conjuncts(Lines, Ind, Type, Conjuncts, VarSet, !IO)
-	; term_to_ite(Term, IfThens, Else) ->
-		write_ite_terms(Lines, Ind, Type, IfThens, Else, VarSet, !IO)
-	; term_to_disj(Term, Disjuncts) ->
-		write_disjuncts(Lines, Ind, Type, Disjuncts, VarSet, !IO)
-	;
-		% Too bad if it is a quantifier, { Goal }, etc.
-		% Also too bad if it contains a pred expression...
-		% You can add pretty things here...
-		write_term(Lines, Ind, VarSet, Term, !IO)
-	).
-
-:- pred term_to_conj(term, list(term)).
-:- mode term_to_conj(in, out) is semidet.
-
-term_to_conj(functor(atom(","), [Head,Term], _), [Head|Tail]) :-
-	( term_to_conj(Term, Tail0) ->
-		Tail = Tail0
-	;
-		Tail = [Term]
-	).
-
 :- pred term_to_disj(term, list(term)).
 :- mode term_to_disj(in, out) is semidet.

@@ -302,123 +271,6 @@
 		Tail = [Term]
 	).

-:- pred term_to_ite(term, list(pair(term)), term).
-:- mode term_to_ite(in, out, out) is semidet.
-
-term_to_ite(functor(atom(";"), [Head,Else0], _), [If - Then|Rest], Else) :-
-	Head = functor(atom("->"), [If, Then], _),
-	( term_to_ite(Else0, Rest0, Else1) ->
-		Rest = Rest0,
-		Else = Else1
-	;
-		Rest = [],
-		Else = Else0
-	).
-
-%------------------------------------------------------------------------------%
-
-:- pred write_conjuncts(lines, int, goal_type, list(term), varset,
-		io__state, io__state).
-:- mode write_conjuncts(in, in, in, in, in, di, uo) is det.
-
-write_conjuncts(_Lines, Ind, Type, [], _VarSet, !IO) :-
-	write_ind(Ind, !IO),
-	(
-		Type = normal,
-		io__write_string("true", !IO)
-	;
-		Type = dcg,
-		io__write_string("{ true }", !IO)
-	).
-
-write_conjuncts(Lines, Ind, Type, [Goal], VarSet, !IO) :-
-	write_goal_term(Lines, Ind, Type, Goal, VarSet, !IO).
-
-write_conjuncts(Lines, Ind, Type, [Goal | Goals], VarSet, !IO) :-
-	Goals = [_|_],
-	write_goal_term(Lines, Ind, Type, Goal, VarSet, !IO),
-	io__write_string(",\n", !IO),
-	write_conjuncts(Lines, Ind, Type, Goals, VarSet, !IO).
-
-%------------------------------------------------------------------------------%
-
-:- pred write_disjuncts(lines, int, goal_type, list(term), varset,
-		io__state, io__state).
-:- mode write_disjuncts(in, in, in, in, in, di, uo) is det.
-
-write_disjuncts(Lines, Ind, Type, Goals, VarSet, !IO) :-
-	write_ind(Ind, !IO),
-	io__write_string("(\n", !IO),
-	write_disjuncts0(Lines, Ind, Type, Goals, VarSet, !IO), io__nl(!IO),
-	write_ind(Ind, !IO),
-	io__write_string(")", !IO).
-
-:- pred write_disjuncts0(lines, int, goal_type, list(term), varset,
-		io__state, io__state).
-:- mode write_disjuncts0(in, in, in, in, in, di, uo) is det.
-
-write_disjuncts0(_Lines, Ind, Type, [], _VarSet, !IO) :-
-	write_ind(Ind, !IO),
-	(
-		Type = normal,
-		io__write_string("fail", !IO)
-	;
-		Type = dcg,
-		io__write_string("{ fail }", !IO)
-	).
-
-write_disjuncts0(Lines, Ind, Type, [Goal], VarSet, !IO) :-
-	write_goal_term(Lines, Ind + 1, Type, Goal, VarSet, !IO), io__nl(!IO).
-
-write_disjuncts0(Lines, Ind, Type, [Goal | Goals], VarSet, !IO) :-
-	Goals = [_|_],
-	write_goal_term(Lines, Ind + 1, Type, Goal, VarSet, !IO), io__nl(!IO),
-	write_ind(Ind, !IO),
-	io__write_string(";\n", !IO),
-	write_disjuncts0(Lines, Ind, Type, Goals, VarSet, !IO).
-
-%------------------------------------------------------------------------------%
-
-:- pred write_ite_terms(lines, int, goal_type, list(pair(term)), term, varset,
-		io__state, io__state).
-:- mode write_ite_terms(in, in, in, in, in, in, di, uo) is det.
-
-write_ite_terms(Lines, Ind, Type, IfThens, Else, VarSet, !IO) :-
-	write_ind(Ind, !IO),
-	io__write_string("(\n", !IO),
-	write_ite_terms0(Lines, Ind, Type, IfThens, VarSet, !IO),
-	write_ind(Ind, !IO),
-	io__write_string(";\n", !IO),
-	write_goal_term(Lines, Ind + 1, Type, Else, VarSet, !IO),
-	io__nl(!IO),
-	write_ind(Ind, !IO),
-	io__write_string(")", !IO).
-
-:- pred write_ite_terms0(lines, int, goal_type, list(pair(term)), varset,
-		io__state, io__state).
-:- mode write_ite_terms0(in, in, in, in, in, di, uo) is det.
-
-write_ite_terms0(_Lines, _Ind, _Type, [], _VarSet, !IO) :-
-	error("no if-thens").
-write_ite_terms0(Lines, Ind, Type, [If - Then], VarSet, !IO) :-
-	write_goal_term(Lines, Ind + 1, Type, If, VarSet, !IO),
-	io__nl(!IO),
-	write_ind(Ind, !IO),
-	io__write_string("->\n", !IO),
-	write_goal_term(Lines, Ind + 1, Type, Then, VarSet, !IO),
-	io__nl(!IO).
-write_ite_terms0(Lines, Ind, Type, [If - Then | Rest], VarSet, !IO) :-
-	Rest = [_|_],
-	write_goal_term(Lines, Ind + 1, Type, If, VarSet, !IO),
-	io__nl(!IO),
-	write_ind(Ind, !IO),
-	io__write_string("->\n", !IO),
-	write_goal_term(Lines, Ind + 1, Type, Then, VarSet, !IO),
-	io__nl(!IO),
-	write_ind(Ind, !IO),
-	io__write_string(";\n", !IO),
-	write_ite_terms0(Lines, Ind, Type, Rest, VarSet, !IO).
-
 %------------------------------------------------------------------------------%

 :- pred cons_decl(string, term, term).
@@ -546,6 +398,14 @@
 		)
 	).

+term_to_goal0("else", [functor(atom("if"), [IfThenTerm],  _), ElseTerm], _,
+		Goal) :-
+	IfThenTerm = functor(atom("then"), [IfTerm, ThenTerm], _),
+	term_to_goal(IfTerm, If),
+	term_to_goal(ThenTerm, Then),
+	term_to_goal(ElseTerm, Else),
+	Goal = ite(If, Then, Else).
+
 term_to_goal0("=", [A, B], Context, =(A, B, Context)).

 term_to_goal0("not", [A], _, not(Goal)) :-
@@ -608,7 +468,8 @@

 write_goal(Lines, Ind, GoalType, ite(If, Then, Else0), VarSet, !IO) :-
 	collect_ite(Else0, IfThens0, Else),
-	write_ite(Lines, Ind, GoalType, [If - Then | IfThens0], Else, VarSet, !IO).
+	write_ite(Lines, Ind, GoalType, [If - Then | IfThens0], Else, VarSet,
+		!IO).

 write_goal(Lines, Ind, GoalType, not(Goal), VarSet, !IO) :-
 	write_ind(Ind, !IO),
Index: samples/alpha.moo
===================================================================
RCS file: /home/mercury1/repository/mercury/extras/moose/samples/alpha.moo,v
retrieving revision 1.2
diff -u -r1.2 alpha.moo
--- samples/alpha.moo	19 Feb 2002 07:49:49 -0000	1.2
+++ samples/alpha.moo	24 Jul 2003 04:27:39 -0000
@@ -41,20 +41,30 @@

 scan([], Toks, [eof|Toks]).
 scan([C|Cs], Toks0, Toks) :-
-	( char__is_whitespace(C) ->
-		scan(Cs, Toks0, Toks)
-	; char__is_digit(C) ->
-		takewhile(char__is_digit, [C|Cs], Digits, Rest),
-		string__from_char_list(Digits, NumStr),
-		Num = string__det_to_int(NumStr),
-		scan(Rest, [num(Num)|Toks0], Toks)
-	; C = ('+') ->
-		scan(Cs, ['+'|Toks0], Toks)
-	; C = ('(') ->
-		scan(Cs, ['('|Toks0], Toks)
-	; C = (')') ->
-		scan(Cs, [')'|Toks0], Toks)
-	;
-		error("expr: syntax error in input")
+	(if
+			char__is_whitespace(C)
+	 then
+			scan(Cs, Toks0, Toks)
+	 else if
+			char__is_digit(C)
+	 then
+			takewhile(char__is_digit, [C|Cs], Digits, Rest),
+			string__from_char_list(Digits, NumStr),
+			Num = string__det_to_int(NumStr),
+			scan(Rest, [num(Num)|Toks0], Toks)
+	 else if
+			C = ('+')
+	 then
+			scan(Cs, ['+'|Toks0], Toks)
+	 else if
+			C = ('(')
+	 then
+			scan(Cs, ['('|Toks0], Toks)
+	 else if
+			C = (')')
+  	 then
+			scan(Cs, [')'|Toks0], Toks)
+	 else
+			error("expr: syntax error in input")
 	).

--------------------------------------------------------------------------
mercury-reviews mailing list
post:  mercury-reviews at cs.mu.oz.au
administrative address: owner-mercury-reviews at cs.mu.oz.au
unsubscribe: Address: mercury-reviews-request at cs.mu.oz.au Message: unsubscribe
subscribe:   Address: mercury-reviews-request at cs.mu.oz.au Message: subscribe
--------------------------------------------------------------------------



More information about the reviews mailing list