Next: , Previous: term_vars, Up: Top   [Contents]


101 term_io

%--------------------------------------------------%
% vim: ft=mercury ts=4 sw=4 et
%--------------------------------------------------%
% Copyright (C) 1994-2006, 2009, 2011-2012 The University of Melbourne.
% Copyright (C) 2014-2024 The Mercury team.
% This file is distributed under the terms specified in COPYING.LIB.
%--------------------------------------------------%
%
% File: term_io.m.
% Main author: fjh.
% Stability: medium to high.
%
% This module provides predicates to write out terms that use the ground
% representation defined in term.m.
%
% Predicates to read in such terms are available in mercury_term_parser.m.
%
% All the operations exported by this module write out a term or a component
% of a term. Each operation is available in four versions.
%
% 1.  A function that converts the given term or component to a string.
% 2a. A predicate that writes out the given term or component
%     to the current output stream,
% 2b. A predicate that writes out the given term or component
%     to a specified output stream,
% 3.  A predicate that writes out the given term or component
%     to any entity that implements the appropriate stream operations.
%
% These versions normally follow a naming scheme:
%
% - X_to_string for version 1,
% - write_X for version 2a and 2b (these two differing only in arity,
%   with 2b having an extra initial output stream argument), and
% - format_X for version 3
%
% where X is the name of the entity being operated on. However, when
% X is a string, the name of the function version will not end in `to_string',
% since that would be strange.
%
% Some operations have more than these four versions, but in every case,
% the extra versions are just old and now obsolete names for one of the four.
%
% The four versions of the same operation will generate the same output,
% they will just put that output in different places.
%
%--------------------------------------------------%
%--------------------------------------------------%

:- module term_io.
:- interface.

:- import_module char.
:- import_module io.
:- import_module ops.
:- import_module stream.
:- import_module term.
:- import_module varset.

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

    % These operations output a term
    % - to a string,
    % - to the current output stream,
    % - to the specified output stream, or
    % - to any implementation of the stream typeclass.
    %
    % They use the Mercury operator table.
    %
    % They all output variable names as specified by the given varset.
    % They write _N for all unnamed variables, with N starting at 0.

:- func term_to_string(varset(T), term(T)) = string.

:- pred write_term(varset(T)::in, term(T)::in, io::di, io::uo) is det.
:- pred write_term(io.text_output_stream::in, varset(T)::in, term(T)::in,
    io::di, io::uo) is det.

:- pred format_term(Stream::in, varset(T)::in, term(T)::in,
    State::di, State::uo) is det <= stream.writer(Stream, string, State).

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

    % These operations output a term
    % - to a string,
    % - to the current output stream,
    % - to the specified output stream, or
    % - to any implementation of the stream typeclass,
    %
    % They use the specified operator table.
    %
    % They all output variable names as specified by the given varset.
    % They write _N for all unnamed variables, with N starting at 0.

:- func term_with_op_table_to_string(OpTable, varset(T), term(T))
    = string <= op_table(OpTable).

:- pred write_term_with_op_table(OpTable::in,
    varset(T)::in, term(T)::in, io::di, io::uo) is det <= op_table(OpTable).
:- pred write_term_with_op_table(io.text_output_stream::in, OpTable::in,
    varset(T)::in, term(T)::in, io::di, io::uo) is det <= op_table(OpTable).

:- pred format_term_with_op_table(Stream::in, OpTable::in,
    varset(T)::in, term(T)::in, State::di, State::uo) is det
    <= (op_table(OpTable), stream.writer(Stream, string, State)).

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

    % These operations output a term
    % - to a string,
    % - to the current output stream,
    % - to the specified output stream, or
    % - to any implementation of the stream typeclass
    % followed by a period and a newline.
    %
    % They use the Mercury operator table.
    %
    % They all output variable names as specified by the given varset.
    % They write _N for all unnamed variables, with N starting at 0.

:- func term_nl_to_string(varset(T), term(T)) = string.

:- pred write_term_nl(varset(T)::in, term(T)::in, io::di, io::uo) is det.
:- pred write_term_nl(io.text_output_stream::in, varset(T)::in, term(T)::in,
    io::di, io::uo) is det.

:- pred format_term_nl(Stream::in, varset(T)::in, term(T)::in,
    State::di, State::uo) is det <= stream.writer(Stream, string, State).

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

    % These operations output a term
    % - to a string,
    % - to the current output stream,
    % - to the specified output stream, or
    % - to any implementation of the stream typeclass
    % followed by a period and a newline.
    %
    % They use the specified operator table.
    %
    % They all output variable names as specified by the given varset.
    % They write _N for all unnamed variables, with N starting at 0.

:- func term_nl_with_op_table_to_string(OpTable, varset(T), term(T))
    = string <= op_table(OpTable).

:- pred write_term_nl_with_op_table(OpTable::in,
    varset(T)::in, term(T)::in, io::di, io::uo) is det <= op_table(OpTable).
:- pred write_term_nl_with_op_table(io.text_output_stream::in, OpTable::in,
    varset(T)::in, term(T)::in, io::di, io::uo) is det <= op_table(OpTable).

:- pred format_term_nl_with_op_table(Stream::in, OpTable::in,
    varset(T)::in, term(T)::in, State::di, State::uo) is det
    <= (op_table(OpTable), stream.writer(Stream, string, State)).

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

    % These operations output either
    % - the value of the variable, if it is bound in the given varset, or
    % - the name of the variable, if it is not bound in the given varset,
    %
    % - to a string,
    % - to the current output stream,
    % - to the specified output stream, or
    % - to any implementation of the stream typeclass
    % followed by a period and a newline.
    %
    % They use the Mercury operator table when printing a value.
    %
    % They all output variable names as specified by the given varset.
    % They write _N for all unnamed variables, with N starting at 0.

:- func variable_to_string(varset(T), var(T)) = string.

:- pred write_variable(varset(T)::in, var(T)::in, io::di, io::uo) is det.
:- pred write_variable(io.text_output_stream::in, varset(T)::in, var(T)::in,
    io::di, io::uo) is det.

:- pred format_variable(Stream::in, varset(T)::in, var(T)::in,
    State::di, State::uo) is det <= stream.writer(Stream, string, State).

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

    % These operations output either
    % - the value of the variable, if it is bound in the given varset, or
    % - the name of the variable, if it is not bound in the given varset,
    %
    % - to a string,
    % - to the current output stream,
    % - to the specified output stream, or
    % - to any implementation of the stream typeclass
    % followed by a period and a newline.
    %
    % They use the specified operator table when printing a value.
    %
    % They all output variable names as specified by the given varset.
    % They write _N for all unnamed variables, with N starting at 0.

:- func variable_with_op_table_to_string(OpTable, varset(T), var(T)) = string
    <= op_table(OpTable).

:- pred write_variable_with_op_table(OpTable::in,
    varset(T)::in, var(T)::in, io::di, io::uo) is det <= op_table(OpTable).
:- pred write_variable_with_op_table(io.text_output_stream::in, OpTable::in,
    varset(T)::in, var(T)::in, io::di, io::uo) is det <= op_table(OpTable).

:- pred format_variable_with_op_table(Stream::in, OpTable::in,
    varset(T)::in, var(T)::in, State::di, State::uo) is det
    <= (op_table(OpTable), stream.writer(Stream, string, State)).

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

    % Convert the given constant to a string.
    %
:- func format_constant(const) = string.
:- func constant_to_string(const) = string.

    % Writes a constant (integer, float, string, or atom) to
    % the current output stream, or to the specified output stream.
    %
:- pred write_constant(const::in, io::di, io::uo) is det.
:- pred write_constant(io.text_output_stream::in, const::in,
    io::di, io::uo) is det.

:- pred format_constant(Stream::in, const::in, State::di, State::uo) is det
    <= stream.writer(Stream, string, State).

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

    % Given a string S, return a version of S in which its characters
    % are escaped if necessary. Enclose the string in quotes.
    %
:- func quoted_atom(string) = string.

    % Given a string S, write a version of S in which its characters
    % are escaped if necessary. Enclose the string in quotes.
    % Write it to the current output stream, or to the specified output stream.
    %
:- pred quote_atom(string::in, io::di, io::uo) is det.
:- pred write_quoted_atom(string::in, io::di, io::uo) is det.
:- pred write_quoted_atom(io.text_output_stream::in, string::in,
    io::di, io::uo) is det.

:- pred quote_atom(Stream::in, string::in, State::di, State::uo) is det
    <= stream.writer(Stream, string, State).
:- pred format_quoted_atom(Stream::in, string::in, State::di, State::uo) is det
    <= stream.writer(Stream, string, State).

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

    % Given a string S, return a version of S in which its characters
    % are escaped if necessary. Do not enclose the string in quotes.
    %
:- func escaped_string(string) = string.

    % Given a string S, write a version of S in which its characters
    % are escaped if necessary. Do not enclose the string in quotes.
    % Write it to the current output stream, or to the specified output stream.
    %
:- pred write_escaped_string(string::in, io::di, io::uo) is det.

:- pred write_escaped_string(Stream::in, string::in, State::di, State::uo)
    is det <= stream.writer(Stream, string, State).
:- pred format_escaped_string(Stream::in, string::in, State::di, State::uo)
    is det <= stream.writer(Stream, string, State).

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

    % Given a string S, return a version of S, with its characters escaped
    % if necessary, in double-quotes.
    %
:- func quoted_string(string) = string.

    % Given a string S, write a version of S, with its characters escaped
    % if necessary, in double-quotes, to the current output stream,
    % or to the specified output stream.
    %
:- pred quote_string(string::in, io::di, io::uo) is det.
:- pred write_quoted_string(string::in, io::di, io::uo) is det.
:- pred write_quoted_string(io.text_output_stream::in, string::in,
    io::di, io::uo) is det.
:- pred quote_string(Stream::in, string::in, State::di, State::uo) is det
    <= stream.writer(Stream, string, State).
:- pred format_quoted_string(Stream::in, string::in, State::di, State::uo)
    is det <= stream.writer(Stream, string, State).

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

    % Given a character C, return C, escaped if necessary.
    % Do not enclose it in single-quotes.
    %
:- func escaped_char(char) = string.
:- func escaped_char_to_string(char) = string.

    % Given a character C, write C, escaped if necessary,
    % and not enclosed in single-quotes, to the current output stream,
    % or to the specified output stream.
    %
:- pred write_escaped_char(char::in, io::di, io::uo) is det.
:- pred write_escaped_char(Stream::in, char::in, State::di, State::uo) is det
    <= stream.writer(Stream, string, State).
:- pred format_escaped_char(Stream::in, char::in, State::di, State::uo) is det
    <= stream.writer(Stream, string, State).

    % A reversible version of escaped_char_to_string.
    %
:- pred string_is_escaped_char(char, string).
:- mode string_is_escaped_char(in, out) is det.
:- mode string_is_escaped_char(out, in) is semidet.

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

    % Given a character C, return C, escaped if necessary, in single-quotes.
    %
:- func quoted_char(char) = string.
:- func quoted_char_to_string(char) = string.

    % Given a character C, write C, escaped if necessary, in single-quotes,
    % to the current output stream, or to the specified output stream.
    %
:- pred quote_char(char::in, io::di, io::uo) is det.
:- pred write_quoted_char(char::in, io::di, io::uo) is det.
:- pred write_quoted_char(io.text_output_stream::in, char::in,
    io::di, io::uo) is det.

:- pred quote_char(Stream::in, char::in, State::di, State::uo) is det
    <= stream.writer(Stream, string, State).
:- pred format_quoted_char(Stream::in, char::in, State::di, State::uo) is det
    <= stream.writer(Stream, string, State).

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


Next: , Previous: term_vars, Up: Top   [Contents]