[m-dev.] string streams and formatting

Michael Day mcda at cat.cs.mu.OZ.AU
Thu Jan 6 12:13:28 AEDT 2000


Hi,

while the interface for io streams is still in flux and rather dogged by
problems regarding determinism and transmuting io__states, I thought it
might be worth clouding the air with a discussion of formatted output.

Also a note on string streams, which appear to be under rather popular
demand. The current implementation states that a string is an instance of
both stream__input and stream__output. Writing to the string appends to
the end of the string. Reading from the string consumes characters from
the front of the string. There is no way to seek on the string. How does
that sound?

But back to formatting. Below is a prototype module for some basic output
formatting, simply consisting of wrapping the thing you want to write in a
format type and writing that instead. Examples:

	write(ascii(Term)),		% replaces io__write
	write(binary(Term)),		% replaces io__write_binary

(Possibly replace ascii(T) and unicode(T) with text(T) and an optional
character encoding specifier, that would appear to be more convenient).

	write(right(80, hex(42))),	% "2A" on right of 80 char field

Fairly straight forward and still lacking in many things, but it seems
like a reasonable way of approaching formatting. The
implementation has been included solely for people who wish to
offer suggestions to improve my Mercury coding style and has no
bearing on the interface or any future implementation. Comments would be
appreciated. Please don't tell me to use a sequence type class again until
we actually have one. Thank you :)

Michael

%-----------------------------------------------------------------------------%
% Copyright (C) 1993-1999 The University of Melbourne.
% This file may only be copied under the terms of the GNU Library General
% Public License - see the file COPYING.LIB in the Mercury distribution.
%-----------------------------------------------------------------------------%
%
% File: format.m.
% Main author: mcda.
% Stability: exceptionally low.
%
% This file provides types for stream formatting.
%
%-----------------------------------------------------------------------------%
%-----------------------------------------------------------------------------%

:- module format.

:- interface.

:- import_module stream, string, char, int, float, list, bool.

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

:- type format__ascii(T)
	--->	ascii(T).

:- type format__unicode(T)
	--->	unicode(T).

:- type format__binary(T)
	--->	binary(T)
	;	binary_big_endian(T)
	;	binary_little_endian(T)
	.

:- type format__packed(T)
	--->	packed(T)
	.

:- type format__field(T)
	--->	left(int, T)
	;	right(int, T)
	;	center(int, T)
	.

:- type format__int
	--->	bin(int)
	;	oct(int)
	;	dec(int)
	;	hex(int)
	;	base(int, int)
	.

:- type format__float
	--->	sci(float)
	;	eng(float)
	;	normal(float)
	.

:- type format__bool
	--->	true_false(bool__bool)
	;	yes_no(bool__bool)
	;	one_zero(bool__bool)
	;	t_nil(bool__bool)
	;	bool(string, string, bool__bool)
	.

:- type format__list(D, T)
	--->	delimit(D, list__list(T))
	.

:- type format__quoted
	--->	quote_char(char)
	;	quote_string(string)
	.

:- type format__special
	--->	newline
	;	backspace
	;	tab
	;	bell
	;	carriage_return
	.

:- instance stream__writable(format__ascii(T)).

:- instance stream__writable(format__unicode(T)).

:- instance stream__writable(format__binary(T)).

:- instance stream__writable(format__field(T)) <= stream__writable(T).

:- instance stream__writable(format__int).

:- instance stream__writable(format__float).

:- instance stream__writable(format__bool).

:- instance stream__writable(format__list(D, T)) <=
	(stream__writable(D), stream__writable(T)).

:- instance stream__writable(format__quoted).

:- instance stream__writable(format__special).

:- instance stream__writable(int).

:- instance stream__writable(float).

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

:- implementation.

:- import_module sstring, std_util.

:- instance stream__writable(ascii(T)) where
	[
		pred(write/3) is write_ascii
	].

:- pred write_ascii(T, S, S) <= stream__output(S).
:- mode write_ascii(in, di, uo) is det.

write_ascii(T, S0, S) :-
	type_to_univ(T, U),
	write_ascii_univ(U, S0, S).

:- pred write_ascii_univ(univ, S, S) <= stream__output(S).
:- mode write_ascii_univ(in, di, uo) is det.

write_ascii_univ(U, S0, S) :-
	(
		univ_to_type(U, String)
	->
		write(quote_string(String), S0, S)
	;
		univ_to_type(U, Char)
	->
		write(quote_char(Char), S0, S)
	;
		univ_to_type(U, Int)
	->
		write(dec(Int), S0, S)
	;
		univ_to_type(U, Float)
	->
		write(normal(Float), S0, S)
	;
		S = S0
	).

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

:- instance stream__writable(field(T)) <= stream__writable(T) where
	[
		pred(write/3) is write_field
	].

:- pred text_pad(int, S, S) <= stream__output(S).
:- mode text_pad(in, di, uo) is det.

text_pad(Count, S0, S) :-
	( Count = 0 ->
		S = S0
	;
		write_char(' ', S0, S1),
		text_pad(Count - 1, S1, S)
	).

:- pred write_field(field(T), S, S) <= (stream__writable(T), stream__output(S)).
:- mode write_field(in, di, uo) is det.

write_field(Field, S0, S) :-
	(
		Field = left(_, T),
		write(T, S0, S)
	;
		Field = right(Width, T),
		write(T, "", String),
		length(String, Length),
		Padding = Width - Length,
		text_pad(Padding, S0, S1),
		write(String, S1, S)
	;
		Field = center(Width, T),
		write(T, "", String),
		length(String, Length),
		Padding = (Width - Length) div 2,
		text_pad(Padding, S0, S1),
		write(String, S1, S)
	).

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

:- instance stream__writable(format__int) where
	[
		pred(write/3) is write_int
	].

:- pred write_int(format__int, S, S) <= stream__output(S).
:- mode write_int(in, di, uo) is det.

write_int(I, S0, S) :-
	(
		I = bin(N), write_int(base(2, N), S0, S)
	;
		I = oct(N), write_int(base(8, N), S0, S)
	;
		I = dec(N), write_int(base(10, N), S0, S)
	;
		I = hex(N), write_int(base(16, N), S0, S)
	;
		I = base(B, N),
		int_to_base_string(N, B, String),
		write(String, S0, S)
	).

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

:- instance stream__writable(format__float) where
	[
		pred(write/3) is write_float
	].

:- pred write_float(format__float, S, S) <= stream__output(S).
:- mode write_float(in, di, uo) is det.

write_float(F, S0, S) :-
	(
		F = sci(N)
	;
		F = eng(N)
	;
		F = normal(N)
	),
	float_to_string(N, String),
	write(String, S0, S).

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

:- instance stream__writable(format__bool) where
	[
		pred(write/3) is write_bool
	].

:- pred write_bool(format__bool, S, S) <= stream__output(S).
:- mode write_bool(in, di, uo) is det.

write_bool(B, S0, S) :-
	(
		B = true_false(V), write_bool(bool("true", "false", V), S0, S)
	;
		B = yes_no(V), write_bool(bool("yes", "no", V), S0, S)
	;
		B = one_zero(V), write_bool(bool("one", "zero", V), S0, S)
	;
		B = t_nil(V), write_bool(bool("t", "nil", V), S0, S)
	;
		B = bool(True, False, V),
		(
			V = yes, write(True, S0, S)
		;
			V = no, write(False, S0, S)
		)
	).

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

:- instance stream__writable(format__list(D, T)) <= (stream__writable(D), stream__writable(T)) where
	[
		pred(write/3) is write_list
	].

:- pred write_list(format__list(D, T), S, S) <= (stream__writable(D), stream__writable(T), stream__output(S)).
:- mode write_list(in, di, uo) is det.

write_list(L, S0, S) :-
	(
		L = delimit(D, List),
		(
			List = [], S = S0
		;
			List = [T|Ts],
			write(T, S0, S1),
			(
				Ts = []
			->
				S = S1
			;
				write(D, S1, S2),
				write(delimit(D, Ts), S2, S)
			)
		)
	).

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

:- instance stream__writable(format__quoted) where
	[
		pred(write/3) is write_quoted
	].

:- pred write_quoted(format__quoted, S, S) <= stream__output(S).
:- mode write_quoted(in, di, uo) is det.

write_quoted(Q) -->
	(
		{ Q = quote_char(Char) },
		write('\''),
		write(Char),
		write('\'')
	;
		{ Q = quote_string(String) },
		write('"'),
		write(String),
		write('"')
	).

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

:- instance stream__writable(format__special) where
	[
		pred(write/3) is write_special
	].

:- pred write_special(special, S, S) <= stream__output(S).
:- mode write_special(in, di, uo) is det.

write_special(C, S0, S) :-
	(
		C = newline, write('\n', S0, S)
	;
		C = backspace, write('\b', S0, S)
	;
		C = tab, write('\t', S0, S)
	;
		C = carriage_return, write('\r', S0, S)
	;
		C = bell, write('\a', S0, S)
	).

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

:- instance stream__writable(int) where
	[
		pred(write/3) is write_real_int
	].

:- pred write_real_int(int, S, S) <= stream__output(S).
:- mode write_real_int(in, di, uo) is det.

write_real_int(I, S0, S) :-
	write(dec(I), S0, S).

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

:- instance stream__writable(float) where
	[
		pred(write/3) is write_real_float
	].

:- pred write_real_float(float, S, S) <= stream__output(S).
:- mode write_real_float(in, di, uo) is det.

write_real_float(F, S0, S) :-
	write(normal(F), S0, S).

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

:- end_module format.

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