This library provides various commonly used DCG primitives acting on
list of character codes. Character classification is based on
code_type/2.
This module started its life as library(http/dcg_basics) to support the
HTTP protocol. Since then, it was increasingly used in code that has no
relation to HTTP and therefore this library was moved to the core
library.
- To be done
- - This is just a starting point. We need a comprehensive set of
generally useful DCG primitives.
- string_without(+EndCodes, -Codes)// is det
- Take as many codes from the input until the next character code
appears in the list EndCodes. The terminating code itself is
left on the input. Typical use is to read upto a defined
delimiter such as a newline or other reserved character. For
example:
...,
string_without("\n", RestOfLine)
- Arguments:
-
EndCodes | - is a list of character codes. |
- See also
- - string//1.
- string(-Codes)// is nondet
- Take as few as possible tokens from the input, taking one more
each time on backtracking. This code is normally followed by a
test for a delimiter. For example:
upto_colon(Atom) -->
string(Codes), ":", !,
{ atom_codes(Atom, Codes) }.
- See also
- - string_without//2.
- blanks// is det
- Skip zero or more white-space characters.
- blank// is semidet
- Take next
space
character from input. Space characters include
newline.
- See also
- - white//0
- nonblanks(-Codes)// is det
- Take all
graph
characters
- nonblank(-Code)// is semidet
- Code is the next non-blank (
graph
) character.
- blanks_to_nl// is semidet
- Take a sequence of blank//0 codes if blanks are followed by a
newline or end of the input.
- whites// is det
- Skip white space inside a line.
- See also
- - blanks//0 also skips newlines.
- white// is semidet
- Take next
white
character from input. White characters do
not include newline.
- alpha_to_lower(?C)// is semidet
- Read a letter (class
alpha
) and return it as a lowercase
letter. If C is instantiated and the DCG list is already bound,
C must be lower
and matches both a lower and uppercase letter.
If the output list is unbound, its first element is bound to C.
For example:
?- alpha_to_lower(0'a, `AB`, R).
R = [66].
?- alpha_to_lower(C, `AB`, R).
C = 97, R = [66].
?- alpha_to_lower(0'a, L, R).
L = [97|R].
- digits(?Chars)// is det
- digit(?Char)// is det
- integer(?Integer)// is det
- Number processing. The predicate digits//1 matches a possibly
empty set of digits, digit//1 processes a single digit and
integer processes an optional sign followed by a non-empty
sequence of digits into an integer.
- float(?Float)// is det
- Process a floating point number. The actual conversion is
controlled by number_codes/2.
- number(+Number)// is det
- number(-Number)// is semidet
- Generate extract a number. Handles both integers and floating
point numbers.
- xinteger(+Integer)// is det
- xinteger(-Integer)// is semidet
- Generate or extract an integer from a sequence of hexadecimal
digits. Hexadecimal characters include both uppercase (A-F) and
lowercase (a-f) letters. The value may be preceded by a sign
(+/-)
- xdigit(-Weight)// is semidet
- True if the next code is a hexdecimal digit with Weight. Weight
is between 0 and 15. Hexadecimal characters include both
uppercase (A-F) and lowercase (a-f) letters.
- xdigits(-WeightList)// is det
- List of weights of a sequence of hexadecimal codes. WeightList
may be empty. Hexadecimal characters include both uppercase
(A-F) and lowercase (a-f) letters.
- eol//
- Matches end-of-line. Matching \r\n, \n or end of input (eos//0).
- eos//
- Matches end-of-input. The implementation behaves as the
following portable implementation:
eos --> call(eos_).
eos_([], []).
- To be done
- - This is a difficult concept and violates the context free
property of DCGs. Explain the exact problems.
- remainder(-List)//
- Unify List with the remainder of the input.
- prolog_var_name(-Name:atom)// is semidet
- Matches a Prolog variable name. Primarily intended to deal with
quasi quotations that embed Prolog variables.
- csym(?Symbol:atom)// is semidet
- Recognise a C symbol according to the
csymf
and csym
code
type classification provided by the C library.
- atom(++Atom)// is det
- Generate codes of Atom. Current implementation uses write/1,
dealing with any Prolog term. Atom must be ground though.
Undocumented predicates
The following predicates are exported, but not or incorrectly documented.
- digit(Arg1, Arg2, Arg3)
- integer(Arg1, Arg2, Arg3)