[m-dev.] Added module qualified backquoted operators to the syntax

Ralph Becket rafe at cs.mu.OZ.AU
Mon Dec 22 16:35:31 AEDT 2003


A revised diff:

Index: doc/reference_manual.texi
===================================================================
RCS file: /home/mercury1/repository/mercury/doc/reference_manual.texi,v
retrieving revision 1.283
diff -u -r1.283 reference_manual.texi
--- doc/reference_manual.texi	5 Dec 2003 05:15:10 -0000	1.283
+++ doc/reference_manual.texi	22 Dec 2003 05:31:25 -0000
@@ -367,8 +367,8 @@
 is a valid tuple term.
 
 An operator term is a term specified using operator notation, as in Prolog.
-Operators can also be formed by enclosing a variable or name between grave
-accents (backquotes).  Any variable or name may
+Operators can also be formed by enclosing a variable or (possibly module
+qualified) name between grave accents (backquotes).  Any variable or name may
 be used as an operator in this way.  If @var{fun} is a variable or name,
 then a term of the form @code{@var{X} `@var{fun}` @var{Y}} is equivalent to 
 @code{@var{fun}(@var{X}, @var{Y})}. The operator is left associative
Index: library/parser.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/parser.m,v
retrieving revision 1.42
diff -u -r1.42 parser.m
--- library/parser.m	26 May 2003 09:00:30 -0000	1.42
+++ library/parser.m	22 Dec 2003 05:30:04 -0000
@@ -453,22 +453,12 @@
 			{ OpPriority = OpPriority0 },
 			{ LeftAssoc = LeftAssoc0 },
 			{ RightAssoc = RightAssoc0 },
-			parser__get_token(OpToken, _),
-			(
-				{ OpToken = name(NameOp) }
-			->
-				{ Op = NameOp },
-				{ VariableTerm = [] }
-			;
-				{ OpToken = variable(VariableOp) },
-				{ Op = "" },
-				parser__add_var(VariableOp, Var),
-				{ VariableTerm = [term__variable(Var)] }
-			),
+			parse_backquoted_operator(Qualifier, Op, VariableTerm),
 			parser__get_token(name("`"), _)
 		;
 			{ Op = Op0 },
 			{ VariableTerm = [] },
+			{ Qualifier = no },
 			parser__get_ops_table(OpTable),
 			{ ops__lookup_infix_op(OpTable, Op,
 					OpPriority, LeftAssoc, RightAssoc) }
@@ -481,10 +471,19 @@
 		parser__parse_term_2(RightPriority, TermKind, RightTerm0),
 		( { RightTerm0 = ok(RightTerm) } ->
 			parser__get_term_context(Context, TermContext),
-			{ OpTerm = term__functor(term__atom(Op),
+			{ OpTerm0 = term__functor(term__atom(Op),
 				list__append(VariableTerm,
 					[LeftTerm, RightTerm]),
 				TermContext) },
+			(
+				{ Qualifier = no },
+				{ OpTerm = OpTerm0 }
+			;
+				{ Qualifier = yes(QTerm) },
+				{ OpTerm = term__functor(term__atom("."),
+					[QTerm, OpTerm0],
+					TermContext) }
+			),
 			parser__parse_rest(MaxPriority, TermKind, OpPriority,
 				OpTerm, Term)
 		;
@@ -506,6 +505,59 @@
 			Term)
 	;
 		{ Term = ok(LeftTerm) }
+	).
+
+
+:- pred parse_backquoted_operator(maybe(term(T)), string, list(term(T)),
+		parser__state(Ops, T), parser__state(Ops, T)) <= op_table(Ops).
+:- mode parse_backquoted_operator(out, out, out, in, out) is semidet.
+
+parse_backquoted_operator(Qualifier, OpName, VariableTerm) -->
+	parser__get_token(Token, _),
+	(
+		{ Token = variable(VariableOp) },
+		{ Qualifier = no },
+		{ OpName = "" },
+		parser__add_var(VariableOp, Var),
+		{ VariableTerm = [variable(Var)] }
+	;
+	  	{ Token = name(OpName0) },
+		{ VariableTerm = [] },
+		parse_backquoted_operator_2(no, Qualifier, OpName0, OpName)
+	).
+
+
+:- pred parse_backquoted_operator_2(maybe(term(T)), maybe(term(T)),
+		string, string,
+		parser__state(Ops, T), parser__state(Ops, T)) <= op_table(Ops).
+:- mode parse_backquoted_operator_2(in, out, in, out, in, out) is semidet.
+
+parse_backquoted_operator_2(Qualifier0, Qualifier, OpName0, OpName) -->
+	( if
+		parser__get_token(name(ModuleSeparator), _),
+		{
+			ModuleSeparator = "."
+		;
+			ModuleSeparator = ":"
+		},
+		parser__get_token(name(OpName1), Context),
+		{ OpName1 \= "`" }
+	  then
+		parser__get_term_context(Context, TermContext),
+	  	{ QTerm1 = term__functor(atom(OpName0), [], TermContext) },
+	  	{
+			Qualifier0 = no,
+			Qualifier1 = yes(QTerm1)
+		;
+			Qualifier0 = yes(QTerm0),
+			Qualifier1 = yes(functor(atom("."), [QTerm0, QTerm1],
+						TermContext))
+		},
+		parse_backquoted_operator_2(Qualifier1, Qualifier,
+			OpName1, OpName)
+	  else
+	  	{ Qualifier = Qualifier0 },
+		{ OpName    = OpName0 }
 	).
 
 %-----------------------------------------------------------------------------%
Index: tests/hard_coded/Mmakefile
===================================================================
RCS file: /home/mercury1/repository/tests/hard_coded/Mmakefile,v
retrieving revision 1.215
diff -u -r1.215 Mmakefile
--- tests/hard_coded/Mmakefile	19 Dec 2003 02:43:59 -0000	1.215
+++ tests/hard_coded/Mmakefile	22 Dec 2003 02:47:41 -0000
@@ -91,6 +91,7 @@
 	impossible_unify \
 	impure_foreign \
 	impure_prune \
+	infix_qualified_ops \
 	integer_test \
 	intermod_c_code \
 	intermod_foreign_type \
Index: tests/hard_coded/infix_qualified_ops.exp
===================================================================
RCS file: tests/hard_coded/infix_qualified_ops.exp
diff -N tests/hard_coded/infix_qualified_ops.exp
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/infix_qualified_ops.exp	22 Dec 2003 02:47:56 -0000
@@ -0,0 +1 @@
+2 + 2 = 4
Index: tests/hard_coded/infix_qualified_ops.m
===================================================================
RCS file: tests/hard_coded/infix_qualified_ops.m
diff -N tests/hard_coded/infix_qualified_ops.m
--- /dev/null	1 Jan 1970 00:00:00 -0000
+++ tests/hard_coded/infix_qualified_ops.m	22 Dec 2003 02:47:24 -0000
@@ -0,0 +1,39 @@
+%-----------------------------------------------------------------------------%
+% infix_qualified_ops.m
+% Ralph Becket <rafe at cs.mu.oz.au>
+% Mon Dec 22 13:45:14 EST 2003
+% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
+%
+% Tests that the parser recognises backquoted, module-qualified operator
+% names.
+%
+%-----------------------------------------------------------------------------%
+
+:- module infix_qualified_ops.
+
+:- interface.
+
+:- import_module io.
+
+
+
+:- pred main(io :: di, io :: uo) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module int, string, list.
+
+%-----------------------------------------------------------------------------%
+
+main(!IO) :-
+    io.format("2 + 2 = %d\n", [i(2 `infix_qualified_ops.add` 2)]).
+
+:- func int `infix_qualified_ops.add` int = int.
+
+X `infix_qualified_ops.add` Y  =  X + Y.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
--------------------------------------------------------------------------
mercury-developers mailing list
Post messages to:       mercury-developers at cs.mu.oz.au
Administrative Queries: owner-mercury-developers at cs.mu.oz.au
Subscriptions:          mercury-developers-request at cs.mu.oz.au
--------------------------------------------------------------------------



More information about the developers mailing list