[m-rev.] diff: remove support for the old-style lambda syntax

Julien Fischer juliensf at cs.mu.OZ.AU
Tue Sep 13 01:16:25 AEST 2005


Estimated hours taken: 1
Branches: main

Remove support for old-style lambda expressions.  These have been deprecated
for a long time now.  Mercury 0.12 issues a warning if you try to use this
syntax.

compiler/prog_io_goal.m:
compiler/superhomogeneous.m
	Do not support parsing old style lambda expressions.

	Do not issue a warning about old-style lambdas being deprecated.

library/ops.m:
	Delete 'lambda' from the operator table.

doc/reference_manual.texi:
	Delete references to the old style lambda expressions.

tests/hard_coded/typeclasses/constrained_lambda.m:
tests/hard_coded/typeclasses/extra_typeinfo.m:
	Update the syntax for lambda expressions.

Julien.

Index: compiler/prog_io_goal.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/prog_io_goal.m,v
retrieving revision 1.34
diff -u -r1.34 prog_io_goal.m
--- compiler/prog_io_goal.m	26 Apr 2005 07:37:59 -0000	1.34
+++ compiler/prog_io_goal.m	12 Sep 2005 14:54:29 -0000
@@ -32,23 +32,9 @@
 	list(prog_var)::out, goal::out, prog_varset::in, prog_varset::out)
 	is det.

-	% parse_lambda_expression/3 converts the first argument to a lambda/2
-	% expression into a list of arguments, a list of their corresponding
-	% modes, and a determinism.
-	% The syntax of a lambda expression is
-	%	`lambda([Var1::Mode1, ..., VarN::ModeN] is Det, Goal)'
-	% but this predicate just parses the first argument, i.e. the
-	% 	`[Var1::Mode1, ..., VarN::ModeN] is Det'
-	% part.
-	%
-:- pred parse_lambda_expression(term::in, list(prog_term)::out,
-	list(mode)::out, determinism::out) is semidet.
-
 	% parse_pred_expression/3 converts the first argument to a :-/2
 	% higher-order pred expression into a list of variables, a list
-	% of their corresponding modes, and a determinism.  This is just
-	% a variant on parse_lambda_expression with a different syntax:
-	% 	`(pred(Var1::Mode1, ..., VarN::ModeN) is Det :- Goal)'.
+	% of their corresponding modes, and a determinism.
 	%
 :- pred parse_pred_expression(term::in, lambda_eval_method::out,
 	list(prog_term)::out, list(mode)::out, determinism::out) is semidet.
@@ -87,10 +73,12 @@
 	% parse_lambda_eval_method/3 extracts the `aditi_bottom_up'
 	% annotation (if any) from a pred expression and returns the
 	% rest of the term.
+	%
 :- pred parse_lambda_eval_method(term(T)::in, lambda_eval_method::out,
 	term(T)::out) is det.

 %-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%

 :- implementation.

@@ -106,6 +94,8 @@
 :- import_module string.
 :- import_module term.

+%-----------------------------------------------------------------------------%
+
 	% Parse a goal.
 	%
 	% We could do some error-checking here, but all errors are picked up
@@ -333,32 +323,6 @@

 %-----------------------------------------------------------------------------%

-parse_lambda_expression(LambdaExpressionTerm, Args, Modes, Det) :-
-	LambdaExpressionTerm = term__functor(term__atom("is"),
-		[LambdaArgsTerm, DetTerm], _),
-	DetTerm = term__functor(term__atom(DetString), [], _),
-	standard_det(DetString, Det),
-	parse_lambda_args(LambdaArgsTerm, Args, Modes),
-	inst_var_constraints_are_consistent_in_modes(Modes).
-
-:- pred parse_lambda_args(term::in, list(prog_term)::out, list(mode)::out)
-	is semidet.
-
-parse_lambda_args(Term, Args, Modes) :-
-	( Term = term__functor(term__atom("[|]"), [Head, Tail], _Context) ->
-		parse_lambda_arg(Head, Arg, Mode),
-		Args = [Arg | Args1],
-		Modes = [Mode | Modes1],
-		parse_lambda_args(Tail, Args1, Modes1)
-	; Term = term__functor(term__atom("[]"), [], _) ->
-		Args = [],
-		Modes = []
-	;
-		Args = [Arg],
-		Modes = [Mode],
-		parse_lambda_arg(Term, Arg, Mode)
-	).
-
 :- pred parse_lambda_arg(term::in, prog_term::out, (mode)::out) is semidet.

 parse_lambda_arg(Term, ArgTerm, Mode) :-
@@ -368,6 +332,9 @@
 	constrain_inst_vars_in_mode(Mode0, Mode).

 %-----------------------------------------------------------------------------%
+%
+% Code for parsing pred/func expressions
+%

 parse_pred_expression(PredTerm, EvalMethod, Args, Modes, Det) :-
 	PredTerm = term__functor(term__atom("is"),
@@ -391,7 +358,7 @@

 parse_func_expression(FuncTerm, EvalMethod, Args, Modes, Det) :-
 	%
-	% parse a func expression with specified modes and determinism
+	% Parse a func expression with specified modes and determinism.
 	%
 	FuncTerm = term__functor(term__atom("is"), [EqTerm, DetTerm], _),
 	EqTerm = term__functor(term__atom("="),
@@ -408,8 +375,8 @@
 		inst_var_constraints_are_consistent_in_modes(Modes)
 	;
 		%
-		% the argument modes default to `in',
-		% the return mode defaults to `out'
+		% The argument modes default to `in',
+		% the return mode defaults to `out'.
 		%
 		in_mode(InMode),
 		out_mode(OutMode),
Index: compiler/superhomogeneous.m
===================================================================
RCS file: /home/mercury1/repository/mercury/compiler/superhomogeneous.m,v
retrieving revision 1.4
diff -u -r1.4 superhomogeneous.m
--- compiler/superhomogeneous.m	12 Sep 2005 05:24:24 -0000	1.4
+++ compiler/superhomogeneous.m	12 Sep 2005 13:27:19 -0000
@@ -443,62 +443,23 @@
         list__append(ConjList1, ConjList2, ConjList),
         conj_list_to_goal(ConjList, GoalInfo, Goal)
     ;
+        % Handle higher-order pred and func expressions.
+        parse_rule_term(Context, RHS, HeadTerm0, GoalTerm1),
+        term__coerce(HeadTerm0, HeadTerm1),
+        parse_purity_annotation(HeadTerm1, LambdaPurity, HeadTerm),
         (
-            % handle lambda expressions
-            parse_lambda_eval_method(RHS, EvalMethod0, RHS1),
-            RHS1 = term__functor(term__atom("lambda"), Args1, _),
-            Args1 = [LambdaExpressionTerm0, GoalTerm0],
-            term__coerce(LambdaExpressionTerm0, LambdaExpressionTerm),
-            parse_lambda_expression(LambdaExpressionTerm, Vars0, Modes0, Det0)
+            parse_pred_expression(HeadTerm, EvalMethod0, Vars0, Modes0, Det0)
         ->
-            LambdaPurity = (pure),
             PredOrFunc = predicate,
             EvalMethod = EvalMethod0,
             Vars1 = Vars0,
             Modes1 = Modes0,
-            Det1 = Det0,
-            GoalTerm1 = GoalTerm0,
-            WarnDeprecatedLambda = yes
+            Det1 = Det0
         ;
-            % handle higher-order pred and func expressions -
-            % same semantics as lambda expressions, different
-            % syntax (the original lambda expression syntax
-            % is now deprecated)
-            parse_rule_term(Context, RHS, HeadTerm0, GoalTerm1),
-            term__coerce(HeadTerm0, HeadTerm1),
-            parse_purity_annotation(HeadTerm1, LambdaPurity,
-                HeadTerm),
-            (
-                parse_pred_expression(HeadTerm, EvalMethod0,
-                    Vars0, Modes0, Det0)
-            ->
-                PredOrFunc = predicate,
-                EvalMethod = EvalMethod0,
-                Vars1 = Vars0,
-                Modes1 = Modes0,
-                Det1 = Det0
-            ;
-                parse_func_expression(HeadTerm, EvalMethod,
-                    Vars1, Modes1, Det1),
-                PredOrFunc = function
-            ),
-            WarnDeprecatedLambda = no
+            parse_func_expression(HeadTerm, EvalMethod, Vars1, Modes1, Det1),
+            PredOrFunc = function
         )
     ->
-        (
-            WarnDeprecatedLambda = yes,
-            report_warning(Context, 0,
-                [words("Warning:"),
-                words("deprecated lambda expression syntax."),
-                nl,
-                words("Lambda expressions with lambda as the"),
-                words("top-level functor are deprecated;"),
-                words("please use the form"),
-                words("using pred instead.")],
-                !IO)
-        ;
-            WarnDeprecatedLambda = no
-        ),
         check_expr_purity(Purity, Context, !ModuleInfo, !IO),
         add_clause__qualify_lambda_mode_list(Modes1, Modes, Context,
             !QualInfo, !IO),
Index: doc/reference_manual.texi
===================================================================
RCS file: /home/mercury1/repository/mercury/doc/reference_manual.texi,v
retrieving revision 1.325
diff -u -r1.325 reference_manual.texi
--- doc/reference_manual.texi	12 Sep 2005 15:07:28 -0000	1.325
+++ doc/reference_manual.texi	12 Sep 2005 15:08:08 -0000
@@ -480,7 +480,6 @@
 <=>                             xfy               920
 =>                              xfy               920
 all                             fxy               950
-lambda                          fxy               950
 promise_equivalent_solutions    fxy               950
 promise_exclusive               fy                950
 promise_exclusive_exhaustive    fy                950
@@ -1403,7 +1402,6 @@
 A lambda expression is a compound term of one of the following forms

 @example
-lambda([Arg1::Mode1, Arg2::Mode2, @dots{}] is Det, Goal)
 pred(Arg1::Mode1, Arg2::Mode2, @dots{}) is Det :- Goal
 pred(Arg1::Mode1, Arg2::Mode2, @dots{}, DCGMode0, DCGMode1) is Det --> DCGGoal
 func(Arg1::Mode1, Arg2::Mode2, @dots{}) = (Result::Mode) is Det :- Goal
@@ -1434,9 +1432,6 @@
 but not in the arguments, the usual Mercury rules for implicit
 quantification apply (@pxref{Implicit quantification}).

-The form of lambda expression using @samp{lambda} as its top level functor
-is deprecated; please use the form using @samp{pred} instead.
-
 The form of lambda expression using @samp{-->} as its top level functor
 is a syntactic abbreviation: an expression of the form

@@ -3868,25 +3863,17 @@
 @end example

 @noindent
-the following three unifications have the same effect:
+the following unifications have the same effect:

 @example
-X = lambda([List::in, Length::out] is det, sum(List, Length))
-Y = (pred(List::in, Length::out) is det :- sum(List, Length))
-Z = sum
+X = (pred(List::in, Length::out) is det :- sum(List, Length))
+Y = sum
 @end example

-In the above example, the type of @samp{X}, @samp{Y}, and @samp{Z} is
+In the above example, the type of @samp{X}, and @samp{Y} is
 @samp{pred(list(int), int)}, which means a predicate of two
 arguments of types @samp{list(int)} and @samp{int} respectively.

-The syntax using @samp{lambda} is deprecated;
-please use the syntax using @samp{pred} instead.
-[The syntax using @samp{lambda} was supported to enable programs to work
-in both Mercury and Prolog, because the syntax using @samp{pred}
-can't be easily emulated in Prolog.  Now that we have implemented
-better debugging environments for Mercury, there is no need for this.]
-
 Similarly, given

 @example
Index: library/ops.m
===================================================================
RCS file: /home/mercury1/repository/mercury/library/ops.m,v
retrieving revision 1.51
diff -u -r1.51 ops.m
--- library/ops.m	29 Aug 2005 03:22:29 -0000	1.51
+++ library/ops.m	12 Sep 2005 13:05:05 -0000
@@ -314,7 +314,6 @@
 ops__op_table("inst", before, fx, 1199).	% Mercury extension
 ops__op_table("instance", before, fx, 1199).	% Mercury extension
 ops__op_table("is", after, xfx, 701).		% ISO Prolog says prec 700
-ops__op_table("lambda", before, fxy, 950).	% Mercury extension
 ops__op_table("mod", after, xfx, 400).		% Standard ISO Prolog
 ops__op_table("mode", before, fx, 1199).	% Mercury extension
 ops__op_table("module", before, fx, 1199).	% Mercury extension
Index: tests/hard_coded/typeclasses/constrained_lambda.m
===================================================================
RCS file: /home/mercury1/repository/tests/hard_coded/typeclasses/constrained_lambda.m,v
retrieving revision 1.1
diff -u -r1.1 constrained_lambda.m
--- tests/hard_coded/typeclasses/constrained_lambda.m	29 Jan 1998 23:51:46 -0000	1.1
+++ tests/hard_coded/typeclasses/constrained_lambda.m	12 Sep 2005 14:49:49 -0000
@@ -11,7 +11,7 @@
 :- import_module list, int.

 main -->
-	{ list__map(lambda([A::in, B::out] is det, p(A,B)), [1,2], X) },
+	{ list__map((pred(A::in, B::out) is det :- p(A,B)), [1,2], X) },
 	io__write(X),
 	io__nl.

Index: tests/hard_coded/typeclasses/extra_typeinfo.m
===================================================================
RCS file: /home/mercury1/repository/tests/hard_coded/typeclasses/extra_typeinfo.m,v
retrieving revision 1.2
diff -u -r1.2 extra_typeinfo.m
--- tests/hard_coded/typeclasses/extra_typeinfo.m	1 Dec 2003 15:56:10 -0000	1.2
+++ tests/hard_coded/typeclasses/extra_typeinfo.m	12 Sep 2005 14:50:58 -0000
@@ -59,7 +59,7 @@
 	% extra argument type_infos for the type variables in the types
 	% of the specialised arguments.
 call_foldl(In, Out0, Out) :-
-	Pred = lambda([Int::in] is semidet, Int = 2),
+	Pred = (pred(Int::in) is semidet :- Int = 2),
 	list_foldl(Pred, [2], In, _, Out0, Out).

 :- pred list_foldl(pred(V), list(V), T, T, U, U) <= foo(T).

--------------------------------------------------------------------------
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