[m-dev.] streams proposal (part 2)

Julien Fischer juliensf at cs.mu.OZ.AU
Tue Feb 21 17:48:29 AEDT 2006


I've been playing around with streams proposal originally posted by Ian here:

<http://www.cs.mu.oz.au/research/mercury/mailing-lists/mercury-developers/mercury-developers.200601/0012.html>

Attached are an extension of Ian's original proposal (streams.m) extended so
that most of the functionality for text streams in the standard library can be
described using streams and a module showing how text streams in the
standard library can be made instances of the stream typeclasses
(stream_io.m).

Some caveats:
	- these module are not really documented, but hopefully the
	  intention should be obvious
	- there are quite a few design alternatives that have been left
          in but commented out
	- quite a few functional dependencies are missing from sub-class
	  decls.

Comments welcome.

Cheers,
Julien.
-------------- next part --------------
%-----------------------------------------------------------------------------r
% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
%-----------------------------------------------------------------------------r
% Copyright (C) 2006 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: stream.m.
% Main authors: Ian MacLarty (maclarty at cs.mu.oz.au).
%              juliensf
% Stability: low.

% XXX a lot of the FDs on sub-classes are missing - they should eventually
%     be implicit.

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

:- module stream.
:- interface.

:- import_module string.

%-----------------------------------------------------------------------------%
%
% Stream errors
%

:- type stream.name == string.

:- type stream.result(T)
    --->    ok(T)
    ;       eof
    ;       some [Error] error(Error) => stream.error(Error).

:- typeclass stream.error(Error) where
[
    % Convert a stream error into a human-readable format.
    % e.g. for use in error messages.
    %
    func error_message(Error) = string
].

%-----------------------------------------------------------------------------%
%
% Streams
%

    % The root of the stream class hierarchy.
    %
:- typeclass stream(Stream, State)
    <= (Stream -> State) where [
    
    % A human readable name describing the stream.
    %
    pred name(Stream::in, stream.name::out, State::di, State::uo) is det,

    % Close the stream.
    % Throws an exception if there is an error while closing the stream.
    %
    pred close(Stream::in, State::di, State::uo) is det
].

%-----------------------------------------------------------------------------%
%
% Input streams
%

% :- typeclass stream.input(Stream, State) <= (Stream -> State) where [].
% 
% :- typeclass stream.input(Stream, Unit, State)
%          <= stream.input(Stream, State) where [
%   pred get(Stream::in, stream.result(Unit)::out, State::di, State::uo) is det
% ].

:- typeclass stream.input(Stream, Unit, State)
        <= stream(Stream, State) where [
    pred get(Stream::in, stream.result(Unit)::out, State::di, State::uo) is det
].

%-----------------------------------------------------------------------------%
%
% Output streams
%

% :- typeclass stream.output(Stream, State) <= (Stream -> State) where [].
% 
% :- typeclass stream.output(Stream, Unit, State)
%         <= stream.output(Stream, State) where [
%     pred put(Stream::in, Unit::in, State::di, State::uo) is det
% ].

:- typeclass stream.output(Stream, Unit, State)
        <= stream(Stream, State) where [
    pred put(Stream::in, Unit::in, State::di, State::uo) is det
].

%-----------------------------------------------------------------------------%
%
% Duplex streams
%

:- typeclass stream.duplex(Stream, Unit, State)
        <= (stream.input(Stream, Unit, State),
            stream.output(Stream, Unit,State)) where [].

%----------------------------------------------------------------------------%
%
% Putback streams
%

:- typeclass stream.putback(Stream, Unit, State)
        <= stream.input(Stream, Unit, State) where [
    
    pred unget(Stream::in, Unit::in, State::di, State::uo) is det
]. 

:- typeclass stream.unbounded_putback(Stream, Unit, State)
    <= stream.putback(Stream, Unit, State) where [].

%----------------------------------------------------------------------------%
%
% Buffered streams
%

% If we want to force buffered streams to be output only then use this
% one and uncomment stream.output/2.
%
%:- typeclass stream.buffered(Stream, State)
%        <= stream.output(Stream, State) where [
%    pred flush(Stream::in, State::di, State::uo) is det
%].

:- typeclass stream.buffered(Stream, State)
        <= stream(Stream, State) where [
    pred flush(Stream::in, State::di, State::uo) is det
].

%----------------------------------------------------------------------------%
%
% Seekable streams
%

:- type stream.whence
    --->    set
    ;       cur
    ;       end.

    % XXX call this random_access?
    %
:- typeclass stream.seekable(Stream, State)
        <= stream(Stream, State) where [
    pred seek(Stream::in, stream.whence::in, int::in, State::di, State::uo)
        is det
].

%----------------------------------------------------------------------------%
%
% Line oriented streams
%

:- typeclass stream.text(Stream, State)
        <= stream(Stream, State) where [
    pred get_line(Stream::in, int::out, State::di, State::uo) is det,
    pred set_line(Stream::in, int::in,  State::di, State::uo) is det
].

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

% It would probably also be useful to have something like the following.

:- typeclass stream.standard_reader(Stream, Unit, State) 
        <= ( stream.input(Stream, Unit, State),
             stream.buffered(Stream, State),
             stream.text(Stream, State)) where [].
    
:- typeclass stream.standard_writer(Stream, Unit, State)
        <= ( stream.output(Stream, Unit, State),
             stream.putback(Stream, Unit, State),
             stream.text(Stream, State)) where [].

%-----------------------------------------------------------------------------%
:- end_module stream.
%-----------------------------------------------------------------------------%
-------------- next part --------------
%-----------------------------------------------------------------------------r
% vim: ft=mercury ts=4 sw=4 et wm=0 tw=0
%-----------------------------------------------------------------------------r

:- module stream_io.
:- interface.

:- import_module char.
:- import_module io.
:- import_module stream.

%----------------------------------------------------------------------------%
%
% I/O errors
%

:- instance stream.error(io.error).

%----------------------------------------------------------------------------%
%----------------------------------------------------------------------------%
% 
% Text streams

:- type line == string.

%----------------------------------------------------------------------------%
%
% Text input streams
%

:- instance stream(io.input_stream, io.state).

% Don't seem to need this.
%:- instance stream.input(io.input_stream, io.state).

:- instance stream.input(io.input_stream, char, io.state).
:- instance stream.input(io.input_stream, line, io.state).

:- instance stream.text(io.input_stream,  io.state).
:- instance stream.putback(io.input_stream, char, io.state).

%----------------------------------------------------------------------------%
%
% Text output streams
%

:- instance stream(io.output_stream, io.state).

% Don't seem to need this.
% :- instance stream.output(io.output_stream, io.state).

:- instance stream.output(io.output_stream, char,   io.state).
:- instance stream.output(io.output_stream, float,  io.state).
:- instance stream.output(io.output_stream, int,    io.state).
:- instance stream.output(io.output_stream, string, io.state).

:- instance stream.text(io.output_stream, io.state).
:- instance stream.buffered(io.output_stream, io.state).

%----------------------------------------------------------------------------%
%
% Binary streams
%

:- instance stream(io.binary_input_stream, io.state).

:- instance stream.seekable(io.binary_input_stream, io.state).

% XXX etc

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

:- implementation.

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

:- instance stream.error(io.error) where [
    func(stream.error_message/1) is io.error_message
].

%----------------------------------------------------------------------------%
%
% Text input streams
%

:- instance stream(io.input_stream, io.state) where [
    pred(name/4)  is io.input_stream_name,
    pred(close/3) is io.close_input
].

% :- instance stream.input(io.input_stream, io.state) where [].

:- instance stream.input(io.input_stream, char, io.state) where [    
    ( get(Stream, Result, !IO) :-
        io.read_char(Stream, Result0, !IO),
        (
            Result0 = ok(Char),
            Result  = ok(Char)
        ;
            Result0 = eof,
            Result  = eof
        ;  
            Result0 = error(IOError),
            Result  = 'new error'(IOError)
        )
    )
]. 

:- instance stream.input(io.input_stream, line, io.state) where [
    ( get(Stream, Result, !IO) :-
        io.read_line_as_string(Stream, Result0, !IO),
        (
            Result0 = ok(Line),
            Result  = ok(Line)
        ;
            Result0 = eof,
            Result  = eof
        ;
            Result0 = error(IOError),
            Result  = 'new error'(IOError)
        )
    )
].

:- instance stream.text(io.input_stream, io.state) where [
    pred(get_line/4) is io.get_line_number,
    pred(set_line/4) is io.set_line_number
].

:- instance stream.putback(io.input_stream, char, io.state) where [
    pred(unget/4) is io.putback_char
].

%----------------------------------------------------------------------------%
%
% Text output streams
%

:- instance stream(io.output_stream, io.state) where [
    pred(name/4)  is io.output_stream_name,
    pred(close/3) is io.close_output
].

% :- instance stream.output(io.output_stream, io.state) where [].

:- instance stream.output(io.output_stream, char, io.state) where [
    ( put(Stream, Char, !IO) :-
        io.write_char(Stream, Char, !IO)
    )
].

:- instance stream.output(io.output_stream, float, io.state) where [
    ( put(Stream, Float, !IO) :-
        io.write_float(Stream, Float, !IO)
    )
].

:- instance stream.output(io.output_stream, int, io.state) where [
    ( put(Stream, Integer, !IO) :-
        io.write_int(Stream, Integer, !IO)
    )
].

:- instance stream.output(io.output_stream, string, io.state) where [
    ( put(Stream, String, !IO) :-
        io.write_string(Stream, String, !IO)
    )
].

:- instance stream.buffered(io.output_stream, io.state) where [
    pred(flush/3) is io.flush_output
].

:- instance stream.text(io.output_stream, io.state) where [
    pred(get_line/4) is io.get_output_line_number,
    pred(set_line/4) is io.set_output_line_number
].

%----------------------------------------------------------------------------%
%
% Binary input streams
%

% XXX This doesn't quite work because (at the moment):
%   
%       io.binary_input_stream  == io.binary_stream
%       io.binary_output_stream == io.binary_stream
%
% and we end up with overlapping instances.

:- instance stream(io.binary_input_stream, io.state) where [
    pred(name/4)  is io.binary_input_stream_name,
    pred(close/3) is io.close_binary_input
]. 

:- instance stream.seekable(io.binary_input_stream, io.state) where [
    (seek(Stream, Whence0, Offset, !IO) :-
        ( 
            Whence0 = set,
            Whence  = set 
        ;
            Whence0 = cur,
            Whence  = cur
        ;
            Whence0 = end,
            Whence  = end
        ),
        io.seek_binary(Stream, Whence, Offset, !IO)
    )
]. 

%----------------------------------------------------------------------------%
:- end_module stream_io.
%----------------------------------------------------------------------------%


More information about the developers mailing list