[m-dev.] formatting, type classes, and existential types

Fergus Henderson fjh at cs.mu.OZ.AU
Sat Jul 4 04:40:08 AEST 1998


On 01-Jul-1998, Peter Schachte <pets at students.cs.mu.oz.au> wrote:
> This is a follow-up to a discussion I had with Fergus and DJ yesterday, sent
> to mercury-developers because I think the wider audience may be interested.
> 
> For a long time, I've believed that the "right" way to do formatted output
> is with a predicate that takes a list of format specifiers:
> 
>   :- pred format(list(format_spec)::in, io_state::di, io_state::uo) is det.
> 
> A reasonable approximation of the definition of format_spec might be:
> 
>   :- type justification ---> left ; right ; center.
>   :- type format_spec --->
> 	(   string(string)
> 	;   int(int)
> 	;   float(float)		% most concise output
> 	;   float(float,int)		% specifying digits of precision
> 	;   expfloat(float,int)		% same, but in exponential notation
> 	;   char(char)
> 	;   justified(format_spec, justification, int)
> 					% give field width and justification
> 	).
> 
> This isn't quite what I wanted, because I find the string/1, int/1, float/1,
> and char/1 wrappers ugly and overly verbose.  But I can live with them if I
> have to.
> 
> This could be implemented in Mercury with no problems.  Unfortunately, it's
> pretty inflexible.  You'd really like to allow users to define their own
> format specifiers. 
> 
> The standard Prolog solution to this problem would be to have a hook
> predicate, which would be declared multifile, to translate a format_spec
> into a string.  format/3 would invoke this for each format spec, and then
> print the result.  No problem. 
> 
> But Mercury's type system won't allow this, as you'd need to have a type
> definition split over multiple files.  Mercury's module system won't allow
> it either, as you'd need to have a predicate split over multiple files, too. 
> 
> When I've mentioned this problem in the past to Mercurians, the answer has
> always been that type classes will allow this.  You just make format_spec be
> a type class that requires a format_spec_to_string operation, and Bob's your
> uncle. 
> 
> Unfortunately, now the list argument to format would be a list of things in
> a type class, rather than things in a type, so Bob's not your uncle after
> all.  The list is actually heterogeneous, and therefore, I was given to
> understand, this requires existential types, and then Bob will be your uncle
> again.
> 
> Now that existential types are (just about) there, I'd like to see how this
> problem can be handled.  What will the person writing the formatting package
> have to write to define the built-in formatting code suggested above? 

I've implemented such a package; it is included at the end of this mail.

The code would be a lot nicer if/when we allow

	(1) abstract `:- instance' declarations

	(2) pred and func definitions inside `:- instance' definitions

	(3) existentially typed data types other than univ

but at least you can do it now.

> And
> what will, say, the implementor of a bignum package have to write to provide
> an implementation of format_spec_to_string for bignums?

If they just want to be able to print bignums, then

	:- instance formattable(bignum) where [
		pred(format/2) is format_bignum
	].
	format_bignum(X) --> ...

is enough.  If the want some kind of special formatting for them, then

	:- type bignum_format ---> whatever(bignum, ...).
	:- instance formattable(bignum_format) where [
		pred(format/2) is format_bignum_format
	].
	format_bignum_format(X) --> ...

Allowing (2) would help a little here.

> Finally, what are
> the prospects for having a version of format/3 which doesn't require you to
> wrap everything?  I'd much rather write (this is in a DCG clause):
> 
> 	format(["The answer is ", N, ".\n"])
> 
> than this:
> 
> 	format([string("The answer is "), int(N), string(".\n")])

That's quite doable.  The drawback is that you basically lose type
inference -- for anything whose argument types include lists, you will
need to explicitly declare whether they should have type `list(T)' or
`format_list'.  My solution below provides this in a submodule, so that
the user can choose whether or not they want to pay that price.

I tested the solution below with my version of the compiler
(MERCURY_COMPILER=~fjh/ws/alpha/mercury/compiler) that includes the
existential types changes, and once I fixed the many compile errors,
it worked fine first time <grin>.

%-----------------------------------------------------------------------------%
:- module format_test.
:- interface.
:- import_module io.

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

:- implementation.
:- import_module format, format__format_list.

main -->
	format(["Hello ", 42, " world\n"]).

%-----------------------------------------------------------------------------%
:- module format.
:- interface.
:- import_module io, char, list.

:- typeclass formattable(T) where [
	pred format(T::in, io__state::di, io__state::uo) is det
].

/* Mercury does not yet support abstract instance declarations. */
% :- instance formattable(int).
% :- instance formattable(string).
% :- instance formattable(float).
% :- instance formattable(char).
% :- instance formattable(list(T)) <= formattable(T).

:- type justification ---> left ; right ; center.
:- type std_format_spec --->
	(   string(string)
	;   int(int)
	;   float(float)		% most concise output
	;   float(float,int)		% specifying digits of precision
	;   expfloat(float,int)		% same, but in exponential notation
	;   char(char)
	;   justified(format_spec, justification, int)
					% give field width and justification
	).
% :- instance formattable(std_format_spec).

:- type format_spec.
:- func +(T) = format_spec <= formattable(T).
% :- instance formattable(format_spec).

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

	:- module format_list.
	:- interface.

	:- type format_list.
	:- func [] = format_list.
	:- func [T | format_list] = format_list <= formattable(T).

	% :- instance formattable(format_list).

	:- implementation.

	/* Mercury does not yet support abstract instance declarations,
	   so this stuff needs to go in the interface, even though logically
	   it is part of the implementation. */

	:- interface.

	:- pred fmt(format_list::in, io__state::di, io__state::uo) is det.

	:- instance formattable(format_list) where [
		pred(format/3) is fmt
	].

	:- implementation.
	
	% :- type format_list == list(format_spec).
	:- type format_list ---> nil ; cons(format_spec, format_list).

	[] = nil.
	[X | Xs] = cons(+X, Xs).

	fmt(nil) --> [].
	fmt(cons(X, Xs)) --> format(X), fmt(Xs).

	:- end_module format_list.

%-----------------------------------------------------------------------------%
:- implementation.
:- import_module std_util.
:- import_module require.

/* Mercury does not yet support abstract instance declarations,
   so this stuff needs to go in the interface, even though logically
   it is part of the implementation. */

:- interface.

:- instance formattable(int) where [
	pred(format/3) is io__write_int
].
:- instance formattable(float) where [
	pred(format/3) is io__write_float
].
:- instance formattable(string) where [
	pred(format/3) is io__write_string
].
:- instance formattable(char) where [
	pred(format/3) is io__write_char
].
:- instance formattable(std_format_spec) where [
	pred(format/3) is format_std_format_spec
].
:- instance formattable(format_spec) where [
	pred(format/3) is format_format_spec
].
:- instance formattable(list(T)) <= formattable(T) where [
	pred(format/3) is format_list
].

:- pred format_format_spec(format_spec::in,
		io__state::di, io__state::uo) is det.

:- pred format_std_format_spec(std_format_spec::in,
		io__state::di, io__state::uo) is det.

:- pred format_list(list(T), io__state, io__state) <= formattable(T).
:- mode format_list(in, di, uo) is det.

:- implementation.

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

format_std_format_spec(int(X)) --> format(X).
format_std_format_spec(string(X)) --> format(X).
format_std_format_spec(float(X)) --> format(X).
format_std_format_spec(char(X)) --> format(X).
format_std_format_spec(float(X, _)) --> format(X). % XXX
format_std_format_spec(expfloat(X, _)) --> format(X). % XXX
format_std_format_spec(justified(X, _, _)) --> format(X). % XXX

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

:- type format_spec ---> format_spec(univ, univ).

+X = format_spec(univ(X), univ_format(X, format)).

:- func univ_format(T, pred(T, io__state, io__state)) = univ.
:- mode univ_format(in, pred(in, di, uo) is det) = out is det.
univ_format(_Val, Func) = univ(Func).

format_format_spec(format_spec(UnivVal, UnivPred)) -->
	{ Val = univ_value(UnivVal) },
	{ det_univ_to_type(UnivPred, Pred0) },
	{ cast_to_higher_order_inst(Pred0, Pred) },
	Pred(Val).

format_list([]) --> [].
format_list([X | Xs]) --> format(X), format_list(Xs).

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

:- pred cast_to_higher_order_inst(pred(T, io__state, io__state),
				  pred(T, io__state, io__state)).
:- mode cast_to_higher_order_inst(in, out(pred(in, di, uo) is det)) is det.
:- pragma c_code(
	cast_to_higher_order_inst(X::in, Y::out(pred(in, di, uo) is det)),
		will_not_call_mercury, "Y = X;").

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

	% univ_value(Univ):
	%	returns the value of the object stored in Univ.
:- some [T] func univ_value(univ) = T.
:- pragma c_code(univ_value(Univ::in) = (Value::out), will_not_call_mercury, "
	TypeInfo_for_T = field(mktag(0), Univ, UNIV_OFFSET_FOR_TYPEINFO);
	Value = field(mktag(0), Univ, UNIV_OFFSET_FOR_DATA);
").

%-----------------------------------------------------------------------------%
:- end_module format.
%-----------------------------------------------------------------------------%

-- 
Fergus Henderson <fjh at cs.mu.oz.au>  |  "I have always known that the pursuit
WWW: <http://www.cs.mu.oz.au/~fjh>  |  of excellence is a lethal habit"
PGP: finger fjh at 128.250.37.3        |     -- the last words of T. S. Garp.



More information about the developers mailing list