[m-dev.] for review: add streams to extras
Peter Ross
peter.ross at miscrit.be
Wed Nov 22 04:12:14 AEDT 2000
Just needs a review of the README.
===================================================================
Estimated hours taken: 50
Mmakefile:
README:
impure.m:
lowlevel.m:
stream.m:
Add the stream library.
Index: Mmakefile
===================================================================
RCS file: Mmakefile
diff -N Mmakefile
--- /dev/null Wed Nov 15 09:24:47 2000
+++ Mmakefile Wed Nov 22 04:10:13 2000
@@ -0,0 +1,3 @@
+MAIN_TARGET=libstream
+
+depend: stream.depend
Index: README
===================================================================
RCS file: README
diff -N README
--- /dev/null Wed Nov 15 09:24:47 2000
+++ README Wed Nov 22 04:10:13 2000
@@ -0,0 +1,26 @@
+This directory contains an implementation of generic IO streams in Mercury.
+
+To build this library you need mutvar.m and semaphore.m from the
+extras/concurrency directory.
+
+The following files implement the stream interfaces at various levels
+
+ stream.m
+ The pure high-level interface. This is the interface external
+ code should use to the stream library. The file also contains
+ examples of extending any stream with infinite putback and/or
+ line numbering.
+
+ lowlevel.m
+ A pure low-level interface. This interface is more useful for
+ using the foreign language binding to define a new stream
+ type. This file also provides implementations of read/write one
+ char which can be used in instance declarations for the
+ highlevel stream typeclasses. This allows an implementor to do
+ the minimum amount of work to achieve an instance of the
+ highlevel stream type class.
+
+ lowlevel.m
+ An impure low-level interface, which provides the same
+ functionality as lowlevel.m except the interface methods are
+ impure.
Index: impure.m
===================================================================
RCS file: impure.m
diff -N impure.m
--- /dev/null Wed Nov 15 09:24:47 2000
+++ impure.m Wed Nov 22 04:10:13 2000
@@ -0,0 +1,135 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2000 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
+%-----------------------------------------------------------------------------%
+%
+% File: impure.m.
+% Main author: petdr
+% Stability: exceptionally low.
+%
+% An impure interface for describing streams. You may want to also look
+% at the pure lowlevel interface in `lowlevel.m'.
+%
+% This file provides a typeclass for people who want to map streams
+% to a foreign language binding while doing the minimum amount of work. In
+% particular you need to write much less foreign language code, since
+% you only need to implement a few impure predicates with a well defined
+% interface.
+%
+% This file provides throwing exceptions, grabbing error messages,
+% results packaged into ok/error/eof, and turning C style handle based
+% IO into Mercury di/uo. That's all it does, but it's something you'll
+% have to do and get right every time you implement a stream, so we have
+% done it for you.
+%
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- module (impure).
+
+:- interface.
+
+:- import_module stream.
+:- import_module char.
+
+ % A handle on the impure stream.
+:- type impure(S).
+
+:- typeclass impure(S) where [
+ % Did an error occur processing the stream?
+ % This predicate must also clear the error status of a
+ % stream after reporting the error.
+ impure pred impure__get_error(S::in, string::out) is semidet
+].
+
+:- typeclass impure__input(S) <= impure(S) where [
+ % Read one character from the stream described by S.
+ % Fail if we reach eof or some error condition.
+ impure pred impure__read_char(S::in, char::out) is semidet,
+
+ % Have we reached the eof for S?
+ semipure pred impure__is_eof(S::in) is semidet
+].
+
+:- typeclass impure__output(S) <= impure(S) where [
+ % Read one character from the current stream.
+ impure pred impure__write_char(S::in, char::in) is semidet
+].
+
+:- pred impure_init(S::in, impure(S)::out, io__state::di, io__state::uo) is det.
+
+%-----------------------------------------------------------------------------%
+
+ % Read one character of input. This read character
+ % implementation can be used in instance declarations for the
+ % stream__input type class.
+
+:- pred pure_read_char(impure(S), stream__result(char),
+ io__state, io__state) <= impure__input(S).
+:- mode pure_read_char(in, out, di, uo) is det.
+
+ % Write one character of output. This write character
+ % implementation can be used in instance declarations for the
+ % stream__output type class.
+
+:- pred pure_write_char(impure(S), char,
+ io__state, io__state) <= impure__output(S).
+:- mode pure_write_char(in, in, di, uo) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module mutvar.
+:- import_module exception, std_util.
+
+:- type impure(S)
+ ---> impure(
+ S, % Handle
+ mutvar(unit) % Mutvar used as a semaphore to
+ % ensure the atomicity of
+ % operations.
+ ).
+
+impure_init(S, impure(S, MVar)) -->
+ mutvar__init(MVar),
+ mutvar__put(MVar, unit).
+
+:- pragma promise_pure(pure_read_char/4).
+pure_read_char(impure(Stream, MVar), Result, IO0, IO) :-
+ mutvar__take(MVar, Unit, IO0, IO1),
+ ( impure impure__read_char(Stream, Chr) ->
+ Result = ok(Chr)
+ ;
+ ( impure impure__get_error(Stream, Error) ->
+ Result = error(Error)
+ ; semipure impure__is_eof(Stream) ->
+ Result = eof
+ ;
+ Error = "read char failed for an unknown reason",
+ Result = error(Error)
+ )
+ ),
+ mutvar__put(MVar, Unit, IO1, IO).
+
+%-----------------------------------------------------------------------------%
+
+:- pragma promise_pure(pure_write_char/4).
+pure_write_char(impure(Stream, MVar), Chr, IO0, IO) :-
+ mutvar__take(MVar, Unit, IO0, IO1),
+ ( impure impure__write_char(Stream, Chr) ->
+ mutvar__put(MVar, Unit, IO1, IO)
+ ;
+ ( impure impure__get_error(Stream, Err0) ->
+ Err = Err0
+ ;
+ Err = "write char failed but there is no error message"
+ ),
+ mutvar__put(MVar, Unit, IO1, IO),
+ throw(stream_error(Err))
+ ).
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
Index: lowlevel.m
===================================================================
RCS file: lowlevel.m
diff -N lowlevel.m
--- /dev/null Wed Nov 15 09:24:47 2000
+++ lowlevel.m Wed Nov 22 04:10:13 2000
@@ -0,0 +1,147 @@
+%-----------------------------------------------------------------------------%
+% Copyright (C) 2000 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
+%-----------------------------------------------------------------------------%
+%
+% File: lowlevel.m.
+% Main author: petdr
+% Stability: exceptionally low.
+%
+% A lowlevel pure interface for describing streams. You may also want
+% to look at the impure lowlevel interface in `impure.m'.
+%
+% This file provides a typeclass for people who want to map streams
+% to a foreign language binding while doing the minimizing the amount of
+% work. In particular you need to write much less foreign language
+% code, since you only need to implement a few predicates with a well
+% defined interface.
+%
+% This file provides throwing exceptions, grabbing error messages and
+% packaging results into ok/error/eof.
+%
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- module lowlevel.
+
+:- interface.
+
+:- import_module stream.
+:- import_module bool, char.
+
+ % A handle on the lowlevel stream.
+:- type lowlevel(S).
+
+:- typeclass lowlevel(S) where [
+ % Did an error occur processing the stream?
+ % This predicate must also clear the error status of a
+ % stream after reporting the error.
+ % The bool indicates whether there was an error. If the
+ % bool is yes, then the string returned holds the error
+ % message.
+ pred get_error(S::in, string::out, bool::out,
+ io__state::di, io__state::uo) is det
+].
+
+:- typeclass lowlevel__input(S) <= lowlevel(S) where [
+ % Attempt to read one character from the stream
+ % described by S.
+ % The bool indicates whether the character was
+ % successfully read.
+ pred read_char(S::in, char::out, bool::out,
+ io__state::di, io__state::uo) is det,
+
+ % The bool will be yes iff S is at the end-of-file (eof).
+ pred is_eof(S::in, bool::out, io__state::di, io__state::uo) is det
+].
+
+:- typeclass output(S) <= lowlevel(S) where [
+ % Attempt to write one character to the current stream.
+ % The bool indicates whether the character was
+ % successfully written.
+ pred write_char(S::in, char::in, bool::out,
+ io__state::di, io__state::uo) is det
+].
+
+:- pred init(S::in, lowlevel(S)::out, io__state::di, io__state::uo) is det.
+
+%-----------------------------------------------------------------------------%
+
+ % Read one character of input. This read character
+ % implementation can be used in instance declarations for the
+ % stream__input type class.
+
+:- pred low_read_char(lowlevel(S), stream__result(char),
+ io__state, io__state) <= lowlevel__input(S).
+:- mode low_read_char(in, out, di, uo) is det.
+
+ % Write one character of output. This write character
+ % implementation can be used in instance declarations for the
+ % stream__output type class.
+
+:- pred low_write_char(lowlevel(S), char,
+ io__state, io__state) <= lowlevel__output(S).
+:- mode low_write_char(in, in, di, uo) is det.
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+:- import_module mutvar.
+:- import_module exception, std_util.
+
+:- type lowlevel(S)
+ ---> lowlevel(
+ S, % Handle
+ mutvar(unit) % Mutvar used as a semaphore to
+ % ensure the atomicity of
+ % operations.
+ ).
+
+init(S, lowlevel(S, MVar)) -->
+ mutvar__init(MVar),
+ mutvar__put(MVar, unit).
+
+low_read_char(lowlevel(Stream, MVar), Result) -->
+ mutvar__take(MVar, Unit),
+ read_char(Stream, Chr, ReadBool),
+ ( { ReadBool = yes } ->
+ { Result = ok(Chr) }
+ ;
+ get_error(Stream, Error, ErrorBool),
+ ( { ErrorBool = yes } ->
+ { Result = error(Error) }
+ ;
+ is_eof(Stream, EofBool),
+ ( { EofBool = yes } ->
+ { Result = eof }
+ ;
+ { ErrorStr = "read char failed for an unknown reason" },
+ { Result = error(ErrorStr) }
+ )
+ )
+ ),
+ mutvar__put(MVar, Unit).
+
+%-----------------------------------------------------------------------------%
+
+low_write_char(lowlevel(Stream, MVar), Chr) -->
+ mutvar__take(MVar, Unit),
+ write_char(Stream, Chr, WriteBool),
+ ( { WriteBool = yes } ->
+ mutvar__put(MVar, Unit)
+ ;
+ get_error(Stream, Err0, ErrorBool),
+ { ErrorBool = yes ->
+ Err = Err0
+ ;
+ Err = "write char failed but there is no error message"
+ },
+ mutvar__put(MVar, Unit),
+ { throw(stream_error(Err)) }
+ ).
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
Index: stream.m
===================================================================
RCS file: stream.m
diff -N stream.m
--- /dev/null Wed Nov 15 09:24:47 2000
+++ stream.m Wed Nov 22 04:10:14 2000
@@ -0,0 +1,436 @@
+%-----------------------------------------------------------------------------%*
+% Copyright (C) 2000 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
+%-----------------------------------------------------------------------------%
+%
+% File: stream.m.
+% Main author: petdr
+% Stability: exceptionally low.
+%
+% This file provides a typeclass for defining streams in Mercury.
+% It is completely pure and you are encouraged to use it to write
+% streams in Mercury. If however you are a library implementor then you
+% may want to look at the lowlevel interface described in lowlevel.m or
+% the impure interface described in impure.m
+%
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
+
+:- module stream.
+
+:- interface.
+
+:- import_module char, io, list.
+
+ % The state of one stream of type S.
+:- type stream(S).
+
+ % The type of exceptions thrown by this module.
+:- type stream_error ---> stream_error(string).
+
+:- type stream__result(T)
+ ---> ok(T)
+ ; eof
+ ; error(string)
+ .
+
+:- type stream__result
+ ---> ok
+ ; eof
+ ; error(string)
+ .
+
+:- type stream__res
+ ---> ok
+ ; error(string)
+ .
+
+%-----------------------------------------------------------------------------%
+
+%
+% The pure interface to streams.
+%
+
+ % The root of the stream class hierarchy
+:- typeclass stream(S) where [
+ % A human-readable name describing the current stream
+ % suitable for use in (e.g.) error messages.
+ func stream__name(S) = string
+].
+
+ % Streams from which you can read input.
+:- typeclass stream__input(S) <= stream(S) where [
+ % Read one character from the stream S.
+ % Errors are reported via the stream__result type.
+ pred stream__read_char(S::in, stream__result(char)::out,
+ io__state::di, io__state::uo) is det
+].
+
+ % Streams to which you can write output.
+:- typeclass stream__output(S) <= stream(S) where [
+ % Write one character to the stream S.
+ % Throws a stream_error exception if a problem occurs.
+ pred stream__write_char(S::in, char::in,
+ io__state::di, io__state::uo) is det
+].
+
+ % Streams which can be both read from and written to.
+:- typeclass stream__duplex(S)
+ <= (stream__input(S), stream__output(S)) where [].
+
+ % Stream for which characters can be put back at the start of
+ % the stream.
+:- typeclass stream__putback(S) <= stream__input(S) where [
+ % Putback one character on the input stream.
+ % The implementation must guarantee at least one
+ % character of putback and throw a stream_error
+ % exception if a problem is encountered during the
+ % putback.
+ pred stream__putback_char(S::in, char::in,
+ io__state::di, io__state::uo) is det
+].
+
+ % Stream with an unbounded amounts of putback.
+ % This adds no new methods, just a guarantee:
+ % there's no limit on the amount of putback except available
+ % memory, so unless you run out of heap space, the putback_char
+ % method must always succeed.
+:- typeclass stream__unbounded_putback(S) <= stream__putback(S) where [].
+
+:- typeclass stream__line(S) <= stream__input(S) where [
+ % Return the line number of the input stream.
+ % Lines are numbered starting from one.
+ pred stream__line_number(S::in, int::out,
+ io__state::di, io__state::uo) is det,
+
+ % Set the line number of the input stream.
+ pred stream__set_line_number(S::in, int::in,
+ io__state::di, io__state::uo) is det
+
+].
+
+%-----------------------------------------------------------------------------%
+
+ %
+ % A input stream with infinite putback.
+ %
+:- type putback(S).
+:- instance stream(putback(S)) <= stream(S).
+:- instance stream__input(putback(S)) <= stream__input(S).
+:- instance stream__putback(putback(S)) <= stream__input(S).
+
+ % Create the putback stream.
+:- pred putback_stream(S::in, putback(S)::out,
+ io__state::di, io__state::uo) is det <= stream__input(S).
+
+ % Retrieve the original stream.
+:- func putback_base_stream(putback(S)) = S.
+
+%-----------------------------------------------------------------------------%
+
+ %
+ % A stream which records which line of the input stream we are
+ % up to. Lines are numbered starting from one.
+ %
+:- type linenumber(S).
+:- instance stream(linenumber(S)) <= stream(S).
+:- instance stream__input(linenumber(S)) <= stream__input(S).
+:- instance stream__putback(linenumber(S)) <= stream__putback(S).
+:- instance stream__line(linenumber(S)) <= stream__input(S).
+
+ % Create a line-number counting stream.
+:- pred linenumber_stream(S::in, linenumber(S)::out,
+ io__state::di, io__state::uo) is det <= stream__input(S).
+
+ % Retrieve the original stream.
+:- func linenumber_base_stream(linenumber(S)) = S.
+
+%-----------------------------------------------------------------------------%
+
+% XXX If/when default type class implementations are introduced,
+% some of the following predicates should probably become members of the
+% relevant type classes.
+
+% Predicates which require an input stream.
+
+ % Reads one line of input from the current input stream.
+:- pred stream__read_line(S::in, stream__result(list(char))::out,
+ io__state::di, io__state::uo) is det <= stream__input(S).
+
+%-----------------------------------------------------------------------------%
+
+% Predicates which require an input stream with putback.
+
+ % Reads a whitespace delimited word from the current input stream.
+:- pred stream__read_word(S::in, stream__result(list(char))::out,
+ io__state::di, io__state::uo) is det <= stream__putback(S).
+
+ % Discards all the whitespace from the input stream.
+:- pred stream__ignore_whitespace(S::in, stream__result::out,
+ io__state::di, io__state::uo) is det <= stream__putback(S).
+
+%-----------------------------------------------------------------------------%
+
+% Predicates which require an output stream.
+% On failure these predicates will throw an stream_error exception.
+
+ % Write the string to the output stream.
+:- pred stream__write_string(S::in, string::in,
+ io__state::di, io__state::uo) is det <= stream__output(S).
+
+%-----------------------------------------------------------------------------%
+
+% Predicates which require an input and a output stream.
+
+ % Echo stream InputS onto stream OutputS.
+ % Errors associated with stream InputS are reported through the
+ % stream__res argument. Errors associated with stream OutputS
+ % throw a stream_error exception.
+:- pred cat(InputS::in, OutputS::in, stream__res::out,
+ io__state::di, io__state::uo) is det
+ <= (stream__input(InputS), stream__output(OutputS)).
+
+%-----------------------------------------------------------------------------%
+
+:- implementation.
+
+ % These two imports are only so that when building a stand-alone
+ % stream library we include the following modules in the
+ % library.
+:- import_module (impure), lowlevel.
+
+:- import_module mutvar.
+:- import_module int, string.
+
+:- type putback(S)
+ ---> pb(
+ S,
+ mutvar(list(char))
+ ).
+
+:- instance stream(putback(S)) <= stream(S) where [
+ (stream__name(pb(S, _)) = stream__name(S))
+].
+
+:- instance stream__input(putback(S)) <= stream__input(S) where [
+ pred(stream__read_char/4) is putback_read_char
+].
+
+:- instance stream__putback(putback(S)) <= stream__input(S) where [
+ pred(stream__putback_char/4) is putback_putback_char
+].
+
+putback_stream(Stream, pb(Stream, MPutbackChars)) -->
+ mutvar__init(MPutbackChars),
+ mutvar__put(MPutbackChars, []).
+
+putback_base_stream(pb(Stream, _)) = Stream.
+
+:- pred putback_read_char(putback(S)::in, stream__result(char)::out,
+ io__state::di, io__state::uo) is det <= stream__input(S).
+
+putback_read_char(pb(Stream, MPutbackChars), Result) -->
+ mutvar__take(MPutbackChars, PutbackChars),
+ (
+ { PutbackChars = [] },
+ { NewPutbackChars = PutbackChars },
+ stream__read_char(Stream, Result)
+ ;
+ { PutbackChars = [Char | NewPutbackChars] },
+ { Result = ok(Char) }
+ ),
+ mutvar__put(MPutbackChars, NewPutbackChars).
+
+:- pred putback_putback_char(putback(S)::in, char::in,
+ io__state::di, io__state::uo) is det <= stream__input(S).
+
+putback_putback_char(pb(_Stream, MPutbackChars), Char) -->
+ mutvar__take(MPutbackChars, PutbackChars),
+ mutvar__put(MPutbackChars, [Char | PutbackChars]).
+
+%-----------------------------------------------------------------------------%
+
+:- type linenumber(S)
+ ---> line(
+ S, % stream
+ mutvar(int) % line number
+ ).
+
+:- instance stream(linenumber(S)) <= stream(S) where [
+ (stream__name(line(S, _)) = stream__name(S))
+].
+
+:- instance stream__input(linenumber(S)) <= stream__input(S) where [
+ pred(stream__read_char/4) is linenumber_read_char
+].
+
+:- instance stream__putback(linenumber(S)) <= stream__putback(S) where [
+ pred(stream__putback_char/4) is linenumber_putback_char
+].
+
+:- instance stream__line(linenumber(S)) <= stream__input(S) where [
+ pred(stream__line_number/4) is linenumber,
+ pred(stream__set_line_number/4) is set_linenumber
+].
+
+linenumber_stream(S, line(S, MLine)) -->
+ mutvar__init(MLine),
+ mutvar__put(MLine, 0).
+
+linenumber_base_stream(line(Stream, _)) = Stream.
+
+:- pred linenumber_read_char(linenumber(S)::in, stream__result(char)::out,
+ io__state::di, io__state::uo) is det <= stream__input(S).
+
+linenumber_read_char(line(Stream, MLine), Result) -->
+ stream__read_char(Stream, Result),
+ ( { Result = ok('\n') } ->
+ mutvar__take(MLine, Line),
+ mutvar__put(MLine, Line + 1)
+ ;
+ []
+ ).
+
+:- pred linenumber_putback_char(linenumber(S)::in, char::in,
+ io__state::di, io__state::uo) is det <= stream__putback(S).
+
+linenumber_putback_char(line(Stream, MLine), Char) -->
+ stream__putback_char(Stream, Char),
+ ( { Char = '\n' } ->
+ mutvar__take(MLine, Line),
+ mutvar__put(MLine, Line - 1)
+ ;
+ []
+ ).
+
+:- pred linenumber(linenumber(S)::in, int::out,
+ io__state::di, io__state::uo) is det.
+
+linenumber(line(_, MLine), Line) -->
+ mutvar__take(MLine, Line),
+ mutvar__put(MLine, Line).
+
+:- pred set_linenumber(linenumber(S)::in, int::in,
+ io__state::di, io__state::uo) is det.
+
+set_linenumber(line(_, MLine), Line) -->
+ mutvar__take(MLine, _OldLine),
+ mutvar__put(MLine, Line).
+
+%-----------------------------------------------------------------------------%
+
+read_line(Stream, Result) -->
+ stream__read_char(Stream, CharResult),
+ (
+ { CharResult = error(Error) },
+ { Result = error(Error) }
+ ;
+ { CharResult = eof },
+ { Result = eof }
+ ;
+ { CharResult = ok(Char) },
+ ( { Char = '\n' } ->
+ { Result = ok([Char]) }
+ ;
+ read_line(Stream, Result0),
+ (
+ { Result0 = ok(Chars) },
+ { Result = ok([Char | Chars]) }
+ ;
+ { Result0 = error(_) },
+ { Result = Result0 }
+ ;
+ { Result0 = eof },
+ { Result = ok([Char]) }
+ )
+ )
+ ).
+
+%-----------------------------------------------------------------------------%
+
+read_word(Stream, Result) -->
+ ignore_whitespace(Stream, WSResult),
+ (
+ { WSResult = error(Error) },
+ { Result = error(Error) }
+ ;
+ { WSResult = eof },
+ { Result = eof }
+ ;
+ { WSResult = ok },
+ read_word_2(Stream, Result)
+ ).
+
+:- pred read_word_2(S::in, stream__result(list(char))::out,
+ io__state::di, io__state::uo) is det <= stream__putback(S).
+
+read_word_2(Stream, Result) -->
+ read_char(Stream, CharResult),
+ (
+ { CharResult = error(Error) },
+ { Result = error(Error) }
+ ;
+ { CharResult = eof },
+ { Result = eof }
+ ;
+ { CharResult = ok(Char) },
+ ( { char__is_whitespace(Char) } ->
+ putback_char(Stream, Char),
+ { Result = ok([]) }
+ ;
+ read_word_2(Stream, Result0),
+ (
+ { Result0 = ok(Chars) },
+ { Result = ok([Char | Chars]) }
+ ;
+ { Result0 = error(_) },
+ { Result = Result0 }
+ ;
+ { Result0 = eof },
+ { Result = ok([Char]) }
+ )
+ )
+ ).
+
+ignore_whitespace(Stream, Result) -->
+ read_char(Stream, CharResult),
+ (
+ { CharResult = error(Error) },
+ { Result = error(Error) }
+ ;
+ { CharResult = eof },
+ { Result = eof }
+ ;
+ { CharResult = ok(Char) },
+ ( { char__is_whitespace(Char) } ->
+ ignore_whitespace(Stream, Result)
+ ;
+ putback_char(Stream, Char),
+ { Result = ok }
+ )
+ ).
+
+%-----------------------------------------------------------------------------%
+
+write_string(Stream, String) -->
+ string__foldl(write_char(Stream), String).
+
+%-----------------------------------------------------------------------------%
+
+cat(In, Out, Result) -->
+ stream__read_char(In, Res),
+ (
+ { Res = ok(Char) },
+ stream__write_char(Out, Char),
+ cat(In, Out, Result)
+ ;
+ { Res = eof },
+ { Result = ok }
+ ;
+ { Res = error(Error) },
+ { Result = error(Error) }
+ ).
+
+%-----------------------------------------------------------------------------%
+%-----------------------------------------------------------------------------%
--------------------------------------------------------------------------
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