![Click to show exports only All predicates](/pldoc/res/private.png)
codesio.pl -- I/O on Lists of Character Codes
This module emulates the SICStus library codesio.pl for reading and
writing from/to lists of character codes. Most of these predicates are
straight calls into similar SWI-Prolog primitives.
This library is based on library(charsio) that originates from Quintus
Prolog. The naming is updated to reflect the ISO naming conventions and
the ISO predicates atom_codes/2, etc are obviously removed from this
library.
- Compatibility
- - SICStus 4
format_to_codes(+Format, +Args, -Codes) is det- Use format/2 to write to a list of character codes.
format_to_codes(+Format, +Args, -Codes, ?Tail) is det- Use format/2 to write to a difference list of character codes.
write_to_codes(+Term, -Codes)- Codes is a list of character codes produced by write/1 on Term.
write_to_codes(+Term, -Codes, ?Tail)- Codes is a difference-list of character codes produced by write/1 on Term.
write_term_to_codes(+Term, -Codes, +Options) is det- True when Codes is a string that matches the output of
write_term/3 using Options.
write_term_to_codes(+Term, -Codes, ?Tail, +Options) is det- True when Codes\Tail is a difference list containing the
character codes that matches the output of write_term/3 using
Options.
read_from_codes(+Codes, -Term) is det- Read Codes into Term.
- Compatibility
- - The SWI-Prolog version does not require Codes to end
in a full-stop.
read_term_from_codes(+Codes, -Term, +Options) is det- Read Codes into Term. Options are processed by read_term/3.
- Compatibility
- - sicstus
open_codes_stream(+Codes, -Stream) is det- Open Codes as an input stream.
- See also
- - open_string/2.
with_output_to_codes(:Goal, Codes) is det- Run Goal with as once/1. Output written to
current_output
is collected in Codes.
with_output_to_codes(:Goal, -Codes, ?Tail) is det- Run Goal with as once/1. Output written to
current_output
is collected in Codes\Tail.
with_output_to_codes(:Goal, -Stream, -Codes, ?Tail) is det- As with_output_to_codes/3, but Stream is unified with the
temporary stream. This predicate exists for compatibility
reasons. In SWI-Prolog, the temporary stream is also available
as
current_output
.