
basics.pl -- Various general DCG utilitiesThis 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.
string_without(+EndCodes, -Codes)// is det
...,
string_without("\n", RestOfLine)
string(-Codes)// is nondet
upto_colon(Atom) -->
string(Codes), ":", !,
{ atom_codes(Atom, Codes) }.
blanks// is det
blank// is semidetspace character from input. Space characters include
newline.
nonblanks(-Codes)// is detgraph characters
nonblank(-Code)// is semidetgraph) character.
blanks_to_nl// is semidet
whites// is det
white// is semidetwhite character from input. White characters do
not include newline.
alpha_to_lower(?C)// is semidetalpha) 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
float(?Float)// is det
number(+Number)// is det
xinteger(+Integer)// is det
xdigit(-Weight)// is semidet
xdigits(-WeightList)// is det
eol//
eos//eos --> call(eos_). eos_([], []).
remainder(-List)//
prolog_var_name(-Name:atom)// is semidet
csym(?Symbol:atom)// is semidetcsymf and csym code
type classification provided by the C library.
atom(++Atom)// is det