1:- module(stream_utils, [
    2	  read_to_end/2,
    3	  read_to_end/3,
    4	  get_line/2, get_line/1, line/1,
    5	  write_string/2, write_string/1,
    6	  %
    7	  file_to_string/2,
    8	  file_to_string/3,
    9	  string_to_file/2,
   10	  %
   11	  output_to_file/2,
   12	  %
   13	  open_input/2, close_input/1,
   14	  open_output/2, close_output/1
   15	]).   16
   17% :- use_module(engine(stream_basic)).
   18% :- use_module(engine(io_basic)).
   19
   20% :- doc(title, "Stream utilities").
   21
   22% :- doc(author,"The Ciao Development Team").
   23
   24% :- doc(module,"This module implements a collection of predicates to
   25%    read/write streams (or files) from/to several sources (lists of
   26%    terms, strings, predicate output, etc.).").
   27
   28% % ===========================================================================
   29% :- doc(section, "Reading/writting from/to streams").
   30
   31% :- pred read_to_end(+Stream, -String) : stream(Stream) => string(String)
   32% # "Reads in @var{String} all the characters from @var{Stream} until an
   33%    EOF is found.".
   34
   35read_to_end(Stream, String) :-
   36	read_to_end(Stream, String, []).
   37
   38% :- pred read_to_end(+Stream, -String, ?Tail): stream(Stream)
   39% # "Reads in the difference list @var{String}-@var{Tail} all the
   40%    characters from @var{Stream} until an EOF is found.".
   41
   42read_to_end(Stream, String, Tail) :-
   43        current_input(OldIn),
   44        set_input(Stream),
   45        read_to_end_(String, Tail),
   46        set_input(OldIn).
   47
   48read_to_end_(L, T) :-
   49        get_code(C),
   50        read_to_end_1(C, L, T).
   51
   52read_to_end_1(-1, T, T) :- !.
   53read_to_end_1(C, [C|L], T) :-
   54        get_code(C1),
   55        read_to_end_1(C1, L, T).
   56
   57% ---------------------------------------------------------------------------
   58
   59% :- doc(get_line(Stream, Line), "Reads from @var{Stream} a line of text
   60%    and unifies @var{Line} with it.  The end of the line can have Unix
   61%    @tt{[10]} or Windows/DOS @tt{[13, 10]} termination, which is not
   62%    included in @var{Line}.  At EOF, the term @tt{end_of_file} is
   63%    returned.").
   64
   65% :- pred get_line(S,L)
   66%          : stream(S)
   67%         => line(L).
   68
   69get_line(Stream, Line) :-
   70        current_input(OldIn),
   71        set_input(Stream),
   72        get_line(Line),
   73        set_input(OldIn).
   74
   75% :- doc(get_line(Line), "Behaves like @tt{current_input(S),
   76%    get_line(S,Line)}.").
   77
   78% :- pred get_line(L) => line(L).
   79
   80get_line(Line) :-
   81        get_code(C),
   82        ( C = -1 -> Line = end_of_file
   83        ; get_line_after(C, Cs),
   84          Line = Cs
   85        ).
   86
   87get_line_after(-1,[]) :- !. % EOF
   88get_line_after(10,[]) :- !. % Newline
   89get_line_after(13, R) :- !, % Return, delete if at end of line
   90        get_code(C),
   91        get_line_after(C, Cs),
   92        ( Cs = [] ->
   93              R = []
   94        ; R = [13|Cs]
   95        ).
   96get_line_after(C, [C|Cs]) :-
   97        get_code(C1),
   98        get_line_after(C1, Cs).
   99
  100% :- doc(doinclude,line/1).
  101
  102% :- prop line/1 + regtype.
  103
  104line(L) :- string(L).
  105line(end_of_file).
  106
  107% ---------------------------------------------------------------------------
  108
  109% :- doc(write_string(Stream, String), "Writes @var{String} onto
  110%    @var{Stream}.").
  111
  112% :- pred write_string(Stream,String)
  113%          : ( stream(Stream), string(String) ).
  114
  115write_string(Stream, S) :-
  116        current_output(OldOut),
  117        set_output(Stream),
  118        write_string(S),
  119        set_output(OldOut).
  120
  121% :- doc(write_string(String), "Behaves like @tt{current_input(S),
  122%    write_string(S, String)}.").
  123
  124% :- pred write_string(String)
  125%          : string(String).
  126
  127write_string(V) :- var(V), !,
  128        throw(error(instantiation_error,write_string/1-1)).
  129write_string([]).
  130write_string([C|Cs]) :- put_code(C), write_string(Cs).
  131
  132% ===========================================================================
  133% :- doc(section, "Reading/writting from/to files").
  134
  135% :- pred file_to_string(+FileName, -String) : sourcename(FileName) => string(String)
  136%    # "Reads all the characters from the file @var{FileName}
  137%       and returns them in @var{String}.".
  138
  139file_to_string(File, String) :-
  140	file_to_string(File, String, []).
  141
  142% :- pred file_to_string(+FileName, -String, ?Tail) : sourcename(FileName) =>
  143%    string(String) # "Reads all the characters from the file
  144%    @var{FileName} and returns them in @var{String}.  @var{Tail} is the
  145%    end of @var{String}.".
  146
  147file_to_string(File, String, Tail) :-
  148        open(File, read, Stream),
  149        read_to_end(Stream, String, Tail),
  150	close(Stream).
  151
  152% ---------------------------------------------------------------------------
  153
  154% :- pred string_to_file(+String, +FileName): (string(String), sourcename(FileName))
  155%    # "Reads all the characters from the string @var{String} and writes
  156%     them to file @var{FileName}.".
  157
  158string_to_file(String, File) :-
  159	open(File, write, Stream),
  160	write_string(Stream, String),
  161	close(Stream).
  162
  163% ---------------------------------------------------------------------------
  164
  165% :- meta_predicate output_to_file(goal, ?).
  166output_to_file(Goal, File) :-
  167	open(File, write, OS),
  168	current_output(CO),
  169	set_output(OS),
  170	call(Goal), % TODO: use port_reify
  171	set_output(CO),
  172	close(OS).
  173
  174% ===========================================================================
  175% :- doc(section, "Structured stream handling").
  176
  177% :- pred open_input(FileName,InputStreams)
  178%          : sourcename(FileName)
  179%         => input_handler(InputStreams).
  180
  181open_input(FileName, i(OldInput, NewInput)) :-
  182        current_input(OldInput),
  183        open(FileName, read, NewInput),
  184        set_input(NewInput).
  185
  186% :- pred close_input(InputStreams)
  187%          : input_handler(InputStreams)
  188%         => input_handler(InputStreams).
  189
  190close_input(i(OldInput, NewInput)) :- !,
  191        set_input(OldInput),
  192        close(NewInput).
  193close_input(X) :-
  194        throw(error(domain_error(open_input_handler, X), close_input/1-1)).
  195
  196% :- pred open_output(FileName,OutputStreams)
  197%          : sourcename(FileName)
  198%         => output_handler(OutputStreams).
  199
  200open_output(FileName, o(OldOutput, NewOutput)) :-
  201        current_output(OldOutput),
  202        open(FileName, write, NewOutput),
  203        set_output(NewOutput).
  204
  205% :- pred close_output(OutputStreams)
  206%          : output_handler(OutputStreams)
  207%         => output_handler(OutputStreams).
  208
  209close_output(o(OldOutput, NewOutput)) :- !,
  210        set_output(OldOutput),
  211        close(NewOutput).
  212close_output(X) :-
  213        throw(error(domain_error(open_output_handler, X), close_output/1-1)).
  214
  215% :- prop input_handler/1 + regtype.
  216%
  217%input_handler(i(Old,New)):-
  218%	stream(Old),
  219%	stream(New).
  220%
  221% :- prop output_handler/1 + regtype.
  222%
  223%output_handler(o(Old,New)):-
  224%	stream(Old),
  225%	stream(New).