[m-rev.] for review: predicate equivalence type and inst declarations

Fergus Henderson fjh at cs.mu.OZ.AU
Wed Mar 13 16:47:49 AEDT 2002


On 11-Mar-2002, Simon Taylor <stayl at cs.mu.OZ.AU> wrote:
> 
> compiler/error_util.m:
> 	Add predicate `pred_or_func_to_string'.

Note that check_typeclass.m already contains such a predicate.
Also hlds_out.m has `pred_or_func_to_str', which is very similar,
but slightly different (it returns "pred" rather than "predicate").

I don't think error_util.m is the best place for this.
Since the pred_or_func type is defined in prog_data.m,
I think the logical place for these predicates is prog_out.m.

But reorganizing that could be done as a separate change.

> Index: NEWS
...
> +* Predicate and function types and modes can now be defined in terms of
> +  higher-order predicate and function types and insts.

This sentence, on its own, is hard to understand.
It makes a bit more sense once you see the example below,
but it would be nicer if it made sense on its own.

Maybe the following would be better?

* Predicate and function type declarations and mode declarations
  can now use higher-order predicate and function types and insts,
  rather than explicitly listing the types and modes of the arguments.

> This is useful
> +  where several predicates or functions must have the the same type and
> +  mode signature.
> +
> +  For example:
> +	:- type foldl_pred(T, U) == pred(T, U, U).
> +	:- inst foldl_pred == pred(in, in, out) is det.

You need parentheses around the `pred(in, in, out) is det' part.

> Index: compiler/equiv_type.m

The documentation at the top of this module should be changed
to explain the new functionality.

It should also be mentioned in compiler/notes/compiler_design.html.

> Index: compiler/make_hlds.m
> +	;
> +		% equiv_type.m should have either set the pred_or_func
> +		% or removed the item from the list.
> +		{ error(
> +		"add_item_decl_pass_1: no pred_or_func on mode declaration") }
> +	).

It would be nicer to use unexpected/2 rather than error/1 here.

> +		;
> +			% equiv_type.m should have either set the
> +			% pred_or_func or removed the item from the list.
> +			{ error(
> +	"module_add_class_method: no pred_or_func on mode declaration") }
> +		)

Likewise here.

> Index: compiler/mercury_to_mercury.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/mercury_to_mercury.m,v
> retrieving revision 1.206
> diff -u -u -r1.206 mercury_to_mercury.m
> --- compiler/mercury_to_mercury.m	26 Feb 2002 02:45:45 -0000	1.206
> +++ compiler/mercury_to_mercury.m	11 Mar 2002 04:05:08 -0000
> @@ -415,39 +415,51 @@
>  
>  mercury_output_item(UnqualifiedItemNames,
>  		pred_or_func(TypeVarSet, InstVarSet, ExistQVars,
> -			PredOrFunc, PredName0, TypesAndModes, Det,
> +			PredOrFunc, PredName0, TypesAndModes,
> +			WithType, WithInst, Det,
>  			_Cond, Purity, ClassContext),
>  		Context) -->
>  	{ maybe_unqualify_sym_name(UnqualifiedItemNames, PredName0, PredName) },
>  	maybe_output_line_number(Context),
>  	(
> -		{ PredOrFunc = predicate },
> -		mercury_format_pred_decl(TypeVarSet, InstVarSet, ExistQVars,
> -			PredName, TypesAndModes, Det, Purity,
> -			ClassContext, Context,
> +		(
> +			{ PredOrFunc = predicate }
> +		;
> +			{ PredOrFunc = function },
> +			{ WithType = yes(_) }
> +		)

Why do functions without a withtype declaration get treated differently?
A brief comment here would help.

Also it might be clear to invert the condition of the if-then-else.

	(	{ PredOrFunc = function },
		{ WithType = no }
	->
		mercury_format_func_decl(...)
	;
		mercury_format_pred_or_func_decl(...)
	)

>  mercury_output_item(UnqualifiedItemNames,
>  		pred_or_func_mode(VarSet, PredOrFunc, PredName0,
> -			Modes, MaybeDet, _Cond),
> +			Modes, WithInst, MaybeDet, _Cond),
>  		Context) -->
>  	{ maybe_unqualify_sym_name(UnqualifiedItemNames, PredName0, PredName) },
>  	maybe_output_line_number(Context),
>  	(
> -		{ PredOrFunc = predicate },
> +		{
> +			PredOrFunc = no
> +		;
> +			PredOrFunc = yes(predicate)
> +		;
> +			PredOrFunc = yes(function),
> +			WithInst = yes(_)
> +		}
> +	->

Likewise here.

>  		% The module name is implied by the qualifier of the
>  		% `:- typeclass declaration'.
>  		{ unqualify_name(Name0, Name) },
>  		(
> -			{ PredOrFunc = predicate },
> -			mercury_format_pred_decl(TypeVarSet, InstVarSet,
> -				ExistQVars, unqualified(Name), TypesAndModes,
> -				Detism, Purity, ClassContext, Context,
> -				"", ",\n\t", "")
> +			(
> +				{ PredOrFunc = predicate }
> +			;
> +				{ PredOrFunc = function },
> +				{ WithType = yes(_) }
> +			)
> +		->
> +			mercury_format_pred_or_func_decl(PredOrFunc,
> +				TypeVarSet, InstVarSet, ExistQVars,
> +				unqualified(Name), TypesAndModes,
> +				WithType, WithInst, Detism, Purity,
> +				ClassContext, Context, "", ",\n\t", "")

And here.

>  		% The module name is implied by the qualifier of the
>  		% `:- typeclass declaration'.
>  		{ unqualify_name(Name0, Name) },
>  		(
> -			{ PredOrFunc = predicate },
> -			mercury_format_pred_mode_decl_2(VarSet,
> +			(
> +				{ PredOrFunc = no }
> +			;
> +				{ PredOrFunc = yes(predicate) }
> +			;
> +				{ PredOrFunc = yes(function) },
> +				{ WithInst = yes(_) }
> +			)
> +		->
> +			mercury_format_pred_or_func_mode_decl_2(VarSet,
>  				unqualified(Name), Modes,
> -				Detism, Context, "", "")
> +				WithInst, Detism, Context, "", "")

And here.

> @@ -1751,7 +1788,15 @@
>  		add_string("(")
>  	),
>  	add_purity_prefix(Purity),
> -	add_string("pred "),
> +
> +	(
> +		{ PredOrFunc = predicate },
> +		add_string("pred ")
> +	;
> +		{ PredOrFunc = function },
> +		add_string("func ")
> +	),

Use hlds_out__pred_or_func_to_str.

> Index: compiler/prog_data.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/compiler/prog_data.m,v
> retrieving revision 1.80
> diff -u -u -r1.80 prog_data.m
> --- compiler/prog_data.m	7 Mar 2002 08:30:16 -0000	1.80
> +++ compiler/prog_data.m	7 Mar 2002 14:27:49 -0000
> +		%	The WithType and WithInst fields are set to `no' by
> +		%	equiv_type.m unless there was an error in the
> +		%	`with_type` and `with_inst` annotations.

I suggest making the comment a bit more explicit, e.g. something along
the lines of this:

		%	The WithType and WithInst fields are for the
		%	`with_type` and `with_inst` annotations, which are
		%	syntactic sugar that is expanded by equiv_type.m.
		%	equiv_type.m will set these fields
		%	to `no' unless there was an error in the
		%	`with_type` and `with_inst` annotations.

(in both places).

> Index: compiler/prog_io.m
...
> +	    ( MaybeDeterminism = yes(_), WithInst = yes(_) ->
> +		R = error("`with_inst` and determinism both specified", Body)
> +	    ; MaybeDeterminism = yes(_), WithType = yes(_) ->
> +		R = error("`with_type` and determinism both specified", Body)
> +	    ; WithInst = yes(_), WithType = no ->
> +		R = error("`with_inst` specified without `with_type`", Body)
...
> +		Result = error("`with_inst` and determinism both specified",
> +				Body)
...
> +			WithInst = error("invalid inst in `with_inst`",
> +					Inst1)
...
> +				Result = error(
> +	"`with_inst` specified, but function arguments don't have modes",
> +					FuncTerm)

There should be test cases for all these errors.

> Index: doc/reference_manual.texi
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/doc/reference_manual.texi,v
> retrieving revision 1.243
> diff -u -u -r1.243 reference_manual.texi
> --- doc/reference_manual.texi	5 Mar 2002 16:55:14 -0000	1.243
> +++ doc/reference_manual.texi	6 Mar 2002 14:35:44 -0000
> @@ -1555,6 +1555,31 @@
>  :- func length(list(T)) = int.
>  @end example
>  
> +A predicate or function can by declared to have a given higher-order
> +type by using `with_type` in the type declaration.

The concept "higher-order type" has not been introduced yet
at this point in the language reference manual.

> This is useful
> +where several predicates or functions need to have the same type
> +signature, which often occurs for typeclass method implementations
> +(@pxref{Type classes}, and for predicates to be passed as higher-order
> +terms (@pxref{Higher-order}). 
> +
> +For example,
> +
> + at example
> +:- type foldl_pred(T, U) == pred(T, U, U).
> +:- type foldl_func(T, U) == (func(T, U) = U).
> +
> +:- pred p(int) `with_type` foldl_pred(T, U).
> +:- pred f(int) `with_type` foldl_func(T, U).

s/pred f/func f/

> + at end example
> +
> + at noindent
> +is equivalent to
> +
> + at example
> +:- pred p(int, T, U, U).
> +:- pred f(int, T, U) = U.
> + at end example

This is definition-by-example.

>  Type variables in predicate and function declarations
>  are implicitly universally quantified by default;
>  that is, the predicate or function may be called with arguments
> @@ -2029,6 +2054,30 @@
>  @example
>  :- func length(list(T)::in) = (int::out).
>  :- pred append(list(T)::in, list(T)::in, list(T)::out).
> +
> +:- pred p `with_type` foldl_pred(T, U) `with_inst` foldl_pred.
> + at end example

This example occurs before `with_inst` has been discussed.
It would be better to delete the example with `with_inst` here,
and instead put it at the end of the section explaining `with_inst`.

> +As for type declarations, a predicate or function can be defined
> +to have a given higher-order inst by using `with_inst` in the
> +mode declaration.
> +
> +For example,
> +
> + at example
> +:- inst foldl_pred == (pred(in, in, out) is det).
> +:- inst foldl_func == (func(in, in) = out is det).
> +
> +:- mode p(in) `with_inst` foldl_pred.
> +:- mode f(in) `with_inst` foldl_func.
> + at end example
> +
> + at noindent
> +is equivalent to
> +
> + at example
> +:- mode p(in, in, in, out) is det.
> +:- mode f(in, in, in) = out is det.
>  @end example

This uses `is det', which has not been explained yet.

I think it might be best to move all the discussion of `with_type`
and `with_inst` into the "Higher order" chapter, and just have
a forward reference to it from this section.

> Index: library/std_util.m
> ===================================================================
> RCS file: /home/mercury1/repository/mercury/library/std_util.m,v
> retrieving revision 1.263
> diff -u -u -r1.263 std_util.m
> --- library/std_util.m	18 Feb 2002 07:01:07 -0000	1.263
> +++ library/std_util.m	19 Feb 2002 14:18:47 -0000
> @@ -102,6 +102,22 @@
>  	%
>  :- func map_maybe(func(T) = U, maybe(T)) = maybe(U).
>  
> +	% map_maybe(P, yes(Value0), yes(Value), Acc0, Acc) :-
> +	%       P(Value, Value, Acc0, Acc).
> +	% map_maybe(_, no, no, Acc, Acc).
> +	%
> +:- pred map_foldl_maybe(pred(T, U, Acc, Acc), maybe(T), maybe(U), Acc, Acc).
> +:- mode map_foldl_maybe(pred(in, out, in, out) is det, in, out, in, out) is det.
> +:- mode map_foldl_maybe(pred(in, out, di, uo) is det, in, out, di, uo) is det.

The name in the comment is wrong: s/may_maybe/map_foldl_maybe/

Also, I suggest s/foldl/fold/g

Finally, it seems silly to put `map_fold_maybe' in the standard
library without having `fold_maybe'.

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