Scryer Prolog documentation

Module charsio

:- use_module(library(charsio)).

High-level predicates to work with chars and strings

This module contains predicates that relates strings of chars to other representations, as well as high-level predicates to read and write chars.

char_type(?Char, ?Type).

Type is one of the categories that Char fits in. At least one of the arguments must be ground. Possible categories are:

  • alnum

  • alpha

  • alphabetic

  • alphanumeric

  • ascii

  • ascii_graphic

  • ascii_punctuation

  • binary_digit

  • control

  • decimal_digit

  • exponent

  • graphic

  • graphic_token

  • hexadecimal_digit

  • layout

  • lower

  • meta

  • numeric

  • octal_digit

  • octet

  • prolog

  • sign

  • solo

  • symbolic_control

  • symbolic_hexadecimal

  • upper

  • lower(Lower)

  • upper(Upper)

  • whitespace

An example:


?- char_type(a, Type).
   Type = alnum
;  Type = alpha
;  Type = alphabetic
;  Type = alphanumeric
;  Type = ascii
;  Type = ascii_graphic
;  Type = hexadecimal_digit
;  Type = lower
;  Type = octet
;  Type = prolog
;  Type = symbolic_control
;  Type = lower("a")
;  Type = upper("A")
;  false.

Note that uppercase and lowercase transformations use a string. This is because some characters do not map 1:1 between lowercase and uppercase.

get_single_char(-Char).

Gets a single char from the current input stream.

read_from_chars(+Chars, -Term).

Given a string made of chars which contains a representation of a Prolog term, Term is the Prolog term represented. Example:


?- read_from_chars("f(x,y).", X).
   X = f(x,y).

read_term_from_chars(+Chars, -Term, +Options).

Like read_from_chars, except the reader is configured according to Options which are those of read_term.


?- read_term_from_chars("f(X,y).", T, [variable_names(['X'=X])]).
   T = f(X,y).

write_term_to_chars(+Term, +Options, -Chars).

Given a Term which is a Prolog term and a set of options, Chars is string representation of that term. Options available are:

  • ignore_ops(+Boolean) if true, the generic term representation is used everywhere. In false (default), operators do not use that generic term representation.
  • max_depth(+N) if the term is nested deeper than N, print the reminder as ellipses. If N = 0 (default), there's no limit.
  • numbervars(+Boolean) if true, replaces $VAR(N) variables with letters, in order. Default is false.
  • quoted(+Boolean) if true, strings and atoms that need quotes to be valid Prolog syntax, are quoted. Default is false.
  • variable_names(+List) assign names to variables in term. List should be a list of terms of format Name=Var.
  • double_quotes(+Boolean) if true, strings are printed in double quotes rather than with list notation. Default is false.

chars_utf8bytes(?Chars, ?Bytes).

Maps a string made of chars with a list of UTF-8 bytes. Some examples:


?- chars_utf8bytes("Prolog", X).
  X = [80,114,111,108,111,103].
?- chars_utf8bytes(X, [226, 136, 145]).
   X = "∑".

get_line_to_chars(+Stream, -Chars, +InitialChars).

Reads chars from stream Stream until it finds a \n character. InitialChars will be appended at the end of Chars

get_n_chars(+Stream, ?N, -Chars).

Read N chars from stream Stream. N can be an integer, in that case only N chars are read, or a variable, unifying N with the number of chars read until it found EOF.

chars_base64(?Chars, ?Base64, +Options).

Relation between a list of characters Cs and its Base64 encoding Bs, also a list of characters.

At least one of the arguments must be instantiated.

Options are:

  • padding(Boolean) Whether to use padding: true (the default) or false.

  • charset(C) Either 'standard' (RFC 4648 §4, the default) or 'url' (RFC 4648 §5).

Example:


?- chars_base64("hello", Bs, []).
   Bs = "aGVsbG8=".