F.2 Library predicates

F.2.1 library(aggregate)

aggregate/3Aggregate bindings in Goal according to Template.
aggregate/4Aggregate bindings in Goal according to Template.
aggregate_all/3Aggregate bindings in Goal according to Template.
aggregate_all/4Aggregate bindings in Goal according to Template.
foreach/2True when the conjunction of _instances_ of Goal created from solutions for Generator is true.
free_variables/4Find free variables in bagof/setof template.

F.2.2 library(ansi_term)

ansi_format/3Format text with ANSI attributes.
ansi_get_color/2Obtain the RGB color for an ANSI color parameter.
ansi_hyperlink/2Create a hyperlink for a terminal emulator.
ansi_hyperlink/3Create a hyperlink for a terminal emulator.
console_color/2Hook that allows for mapping abstract terms to concrete ANSI attributes.

F.2.3 library(apply)

convlist/3Similar to maplist/3, but elements for which call(Goal, ElemIn, _) fails are omitted from ListOut.
exclude/3Filter elements for which Goal fails.
foldl/4Fold an ensemble of _m_ (0 <= _m_ <= 4) lists of length _n_ head-to-tail ("fold-left"), using columns of _m_ list elements as arguments for Goal.
foldl/5Fold an ensemble of _m_ (0 <= _m_ <= 4) lists of length _n_ head-to-tail ("fold-left"), using columns of _m_ list elements as arguments for Goal.
foldl/6Fold an ensemble of _m_ (0 <= _m_ <= 4) lists of length _n_ head-to-tail ("fold-left"), using columns of _m_ list elements as arguments for Goal.
foldl/7Fold an ensemble of _m_ (0 <= _m_ <= 4) lists of length _n_ head-to-tail ("fold-left"), using columns of _m_ list elements as arguments for Goal.
include/3Filter elements for which Goal succeeds.
maplist/2True if Goal is successfully applied on all matching elements of the list.
maplist/3True if Goal is successfully applied on all matching elements of the list.
maplist/4True if Goal is successfully applied on all matching elements of the list.
maplist/5True if Goal is successfully applied on all matching elements of the list.
partition/4Filter elements of List according to Pred.
partition/5Filter List according to Pred in three sets.
scanl/4Scan an ensemble of _m_ (0 <= _m_ <= 4) lists of length _n_ head-to-tail ("scan-left"), using columns of _m_ list elements as arguments for Goal.
scanl/5Scan an ensemble of _m_ (0 <= _m_ <= 4) lists of length _n_ head-to-tail ("scan-left"), using columns of _m_ list elements as arguments for Goal.
scanl/6Scan an ensemble of _m_ (0 <= _m_ <= 4) lists of length _n_ head-to-tail ("scan-left"), using columns of _m_ list elements as arguments for Goal.
scanl/7Scan an ensemble of _m_ (0 <= _m_ <= 4) lists of length _n_ head-to-tail ("scan-left"), using columns of _m_ list elements as arguments for Goal.

F.2.4 library(assoc)

assoc_to_list/2Translate assoc into a pairs list
assoc_to_keys/2Translate assoc into a key list
assoc_to_values/2Translate assoc into a value list
empty_assoc/1Test/create an empty assoc
gen_assoc/3Non-deterministic enumeration of assoc
get_assoc/3Get associated value
get_assoc/5Get and replace associated value
list_to_assoc/2Translate pair list to assoc
map_assoc/2Test assoc values
map_assoc/3Map assoc values
max_assoc/3Max key-value of an assoc
min_assoc/3Min key-value of an assoc
ord_list_to_assoc/2Translate ordered list into an assoc
put_assoc/4Add association to an assoc

F.2.5 library(broadcast)

broadcast/1Send event notification
broadcast_request/1Request all agents
listen/2Listen to event notifications
listen/3Listen to event notifications
unlisten/1Stop listening to event notifications
unlisten/2Stop listening to event notifications
unlisten/3Stop listening to event notifications
listening/3Who is listening to event notifications?

F.2.6 library(charsio)

atom_to_chars/2Convert Atom into a list of character codes.
atom_to_chars/3Convert Atom into a difference list of character codes.
format_to_chars/3Use format/2 to write to a list of character codes.
format_to_chars/4Use format/2 to write to a difference list of character codes.
number_to_chars/2Convert Atom into a list of character codes.
number_to_chars/3Convert Number into a difference list of character codes.
open_chars_stream/2Open Codes as an input stream.
read_from_chars/2Read Codes into Term.
read_term_from_chars/3Read Codes into Term.
with_output_to_chars/2Run Goal as with once/1.
with_output_to_chars/3Run Goal as with once/1.
with_output_to_chars/4Same as with_output_to_chars/3 using an explicit stream.
write_to_chars/2Write a term to a code list.
write_to_chars/3Write a term to a code list.

F.2.7 library(check)

check/0Run all consistency checks defined by checker/2.
checker/2Register code validation routines.
list_autoload/0Report predicates that may be auto-loaded.
list_cross_module_calls/0List calls from one module to another using Module:Goal where the callee is not defined exported, public or multifile, i.e., where the callee should be considered _private_.
list_format_errors/0List argument errors for format/2,3.
list_format_errors/1List argument errors for format/2,3.
list_rationals/0List rational numbers that appear in clauses.
list_rationals/1List rational numbers that appear in clauses.
list_redefined/0Lists predicates that are defined in the global module =user= as well as in a normal module; that is, predicates for which the local definition overrules the global default definition.
list_strings/0List strings that appear in clauses.
list_strings/1List strings that appear in clauses.
list_trivial_fails/0List goals that trivially fail because there is no matching clause.
list_trivial_fails/1List goals that trivially fail because there is no matching clause.
list_undefined/0Report undefined predicates.
list_undefined/1Report undefined predicates.
list_void_declarations/0List predicates that have declared attributes, but no clauses.
string_predicate/1Multifile hook to disable list_strings/0 on the given predicate.
trivial_fail_goal/1Multifile hook that tells list_trivial_fails/0 to accept Goal as valid.
valid_string_goal/1Multifile hook that qualifies Goal as valid for list_strings/0.

F.2.8 library(clpb)

labeling/1Enumerate concrete solutions.
random_labeling/2Select a single random solution.
sat/1True iff Expr is a satisfiable Boolean expression.
sat_count/2Count the number of admissible assignments.
taut/2Tautology check.
weighted_maximum/3Enumerate weighted optima over admissible assignments.

F.2.9 library(clpfd)

#/\/2P and Q hold.
#</2The arithmetic expression X is less than Y.
#<==/2Q implies P.
#<==>/2P and Q are equivalent.
#=/2The arithmetic expression X equals Y.
#=</2The arithmetic expression X is less than or equal to Y.
#==>/2P implies Q.
#>/2Same as Y #< X.
#>=/2Same as Y #=< X.
#\/1Q does _not_ hold.
#\/2Either P holds or Q holds, but not both.
#\//2P or Q holds.
#\=/2The arithmetic expressions X and Y evaluate to distinct integers.
all_different/1Like all_distinct/1, but with weaker propagation.
all_distinct/1True iff Vars are pairwise distinct.
automaton/3Describes a list of finite domain variables with a finite automaton.
automaton/8Describes a list of finite domain variables with a finite automaton.
chain/2Zs form a chain with respect to Relation.
circuit/1True iff the list Vs of finite domain variables induces a Hamiltonian circuit.
cumulative/1Equivalent to cumulative(Tasks, [limit(1)]).
cumulative/2Schedule with a limited resource.
disjoint2/1True iff Rectangles are not overlapping.
element/3The N-th element of the list of finite domain variables Vs is V.
empty_fdset/1Set is the empty FD set.
empty_interval/2Min..Max is an empty interval.
fd_degree/2Degree is the number of constraints currently attached to Var.
fd_dom/2Dom is the current domain (see in/2) of Var.
fd_inf/2Inf is the infimum of the current domain of Var.
fd_set/2Set is the FD set representation of the current domain of Var.
fd_size/2Reflect the current size of a domain.
fd_sup/2Sup is the supremum of the current domain of Var.
fd_var/1True iff Var is a CLP(FD) variable.
fdset_add_element/3Set2 is the same FD set as Set1, but with the integer Elt added.
fdset_complement/2The FD set Complement is the complement of the FD set Set.
fdset_del_element/3Set2 is the same FD set as Set1, but with the integer Elt removed.
fdset_disjoint/2The FD sets Set1 and Set2 have no elements in common.
fdset_eq/2True if the FD sets Set1 and Set2 are equal, i.
fdset_intersect/2The FD sets Set1 and Set2 have at least one element in common.
fdset_intersection/3Intersection is an FD set (possibly empty) of all elements that the FD sets Set1 and Set2 have in common.
fdset_interval/3Interval is a non-empty FD set consisting of the single interval Min..Max.
fdset_max/2Max is the upper bound (supremum) of the non-empty FD set Set.
fdset_member/2The integer Elt is a member of the FD set Set.
fdset_min/2Min is the lower bound (infimum) of the non-empty FD set Set.
fdset_parts/4Set is a non-empty FD set representing the domain Min..Max \/ Rest, where Min..Max is a non-empty interval (see fdset_interval/3) and Rest is another FD set (possibly empty).
fdset_singleton/2Set is the FD set containing the single integer Elt.
fdset_size/2Size is the number of elements of the FD set Set, or the atom *sup* if Set is infinite.
fdset_subset/2The FD set Set1 is a (non-strict) subset of Set2, i.
fdset_subtract/3The FD set Difference is Set1 with all elements of Set2 removed, i.
fdset_to_list/2List is a list containing all elements of the finite FD set Set, in ascending order.
fdset_to_range/2Domain is a domain equivalent to the FD set Set.
fdset_union/2The FD set Union is the n-ary union of all FD sets in the list Sets.
fdset_union/3The FD set Union is the union of FD sets Set1 and Set2.
global_cardinality/2Global Cardinality constraint.
global_cardinality/3Global Cardinality constraint.
in/2Var is an element of Domain.
in_set/2Var is an element of the FD set Set.
indomain/1Bind Var to all feasible values of its domain on backtracking.
ins/2The variables in the list Vars are elements of Domain.
is_fdset/1Set is currently bound to a valid FD set.
label/1Equivalent to labeling([], Vars).
labeling/2Assign a value to each variable in Vars.
lex_chain/1Lists are lexicographically non-decreasing.
list_to_fdset/2Set is an FD set containing all elements of List, which must be a list of integers.
range_to_fdset/2Set is an FD set equivalent to the domain Domain.
scalar_product/4True iff the scalar product of Cs and Vs is in relation Rel to Expr.
serialized/2Describes a set of non-overlapping tasks.
sum/3The sum of elements of the list Vars is in relation Rel to Expr.
transpose/2Transpose a list of lists of the same length.
tuples_in/2True iff all Tuples are elements of Relation.
zcompare/3Analogous to compare/3, with finite domain variables A and B.

F.2.10 library(clpqr)

entailed/1Check if constraint is entailed
inf/2Find the infimum of an expression
sup/2Find the supremum of an expression
minimize/1Minimizes an expression
maximize/1Maximizes an expression
bb_inf/3Infimum of expression for mixed-integer problems
bb_inf/4Infimum of expression for mixed-integer problems
bb_inf/5Infimum of expression for mixed-integer problems
dump/3Dump constraints on variables

F.2.11 library(csv)

csv_options/2Compiled is the compiled representation of the CSV processing options as they may be passed into csv//2, etc.
csv_read_file/2Read a CSV file into a list of rows.
csv_read_file/3Read a CSV file into a list of rows.
csv_read_file_row/3True when Row is a row in File.
csv_read_row/3Read the next CSV record from Stream and unify the result with Row.
csv_read_stream/3Read CSV data from Stream.
csv_write_file/2Write a list of Prolog terms to a CSV file.
csv_write_file/3Write a list of Prolog terms to a CSV file.
csv_write_stream/3Write the rows in Data to Stream.
csv//1Prolog DCG to‘read/write' CSV data.
csv//2Prolog DCG to‘read/write' CSV data.

F.2.12 library(dcgbasics)

alpha_to_lower//1Read a letter (class =alpha=) and return it as a lowercase letter.
atom//1Generate codes of Atom.
blank//0Take next =space= character from input.
blanks//0Skip zero or more white-space characters.
blanks_to_nl//0Take a sequence of blank//0 codes if blanks are followed by a newline or end of the input.
csym//1Recognise a C symbol according to the‘csymf` and‘csym` code type classification provided by the C library.
digit//1Number processing.
digits//1Number processing.
eol//0Matches end-of-line.
eos//0Matches end-of-input.
float//1Process a floating point number.
integer//1Number processing.
nonblank//1Code is the next non-blank (=graph=) character.
nonblanks//1Take all =graph= characters.
number//1Generate extract a number.
prolog_var_name//1Matches a Prolog variable name.
remainder//1Unify List with the remainder of the input.
string//1Take as few as possible tokens from the input, taking one more each time on backtracking.
string_without//2Take as many codes from the input until the next character code appears in the list EndCodes.
white//0Take next =white= character from input.
whites//0Skip white space _inside_ a line.
xdigit//1True if the next code is a hexdecimal digit with Weight.
xdigits//1List of weights of a sequence of hexadecimal codes.
xinteger//1Generate or extract an integer from a sequence of hexadecimal digits.

F.2.13 library(dcghighorder)

foreach//2Generate a list from the solutions of Generator.
foreach//3Generate a list from the solutions of Generator.
optional//2Perform an optional match, executing Default if Match is not matched.
sequence//2Match or generate a sequence of Element.
sequence//3Match or generate a sequence of Element where each pair of elements is separated by Sep.
sequence//5Match or generate a sequence of Element enclosed by Start end End, where each pair of elements is separated by Sep.

F.2.14 library(debug)

assertion/1Acts similar to C assert() macro.
assertion_failed/2This hook is called if the Goal of assertion/1 fails.
debug/1Add/remove a topic from being printed.
debug/3Format a message if debug topic is enabled.
debug_message_context/1Specify additional context for debug messages.
debug_print_hook/3Hook called by debug/3.
debugging/1Examine debug topics.
debugging/2Examine debug topics.
list_debug_topics/0List currently known topics for debug/3 and their setting.
list_debug_topics/1List currently known topics for debug/3 and their setting.
nodebug/1Add/remove a topic from being printed.

F.2.15 library(dicts)

dict_fill/4Implementation for the dicts_to_same_keys/3‘OnEmpty` closure that fills new cells with a copy of ValueIn.
dict_keys/2True when Keys is an ordered set of the keys appearing in Dict.
dict_size/2True when KeyCount is the number of keys in Dict.
dicts_join/3Join dicts in Dicts that have the same value for Key, provided they do not have conflicting values on other keys.
dicts_join/4Join two lists of dicts (Dicts1 and Dicts2) on Key.
dicts_same_keys/2True if List is a list of dicts that all have the same keys and Keys is an ordered set of these keys.
dicts_same_tag/2True when List is a list of dicts that all have the tag Tag.
dicts_slice/3DictsOut is a list of Dicts only containing values for Keys.
dicts_to_compounds/4True when Dicts and Compounds are lists of the same length and each element of Compounds is a compound term whose arguments represent the values associated with the corresponding keys in Keys.
dicts_to_same_keys/3DictsOut is a copy of DictsIn, where each dict contains all keys appearing in all dicts of DictsIn.

F.2.16 library(error)

current_encoding/1True if Name is the name of a supported encoding.
current_type/3True when Type is a currently defined type and Var satisfies Type of the body term Body succeeds.
domain_error/2The argument is of the proper type, but has a value that is outside the supported values.
existence_error/2Culprit is of the correct type and correct domain, but there is no existing (external) resource of type ObjectType that is represented by it.
existence_error/3Culprit is of the correct type and correct domain, but there is no existing (external) resource of type ObjectType that is represented by it in the provided set.
has_type/2True if Term satisfies Type.
instantiation_error/1An argument is under-instantiated.
is_of_type/2True if Term satisfies Type.
must_be/2True if Term satisfies the type constraints for Type.
permission_error/3It is not allowed to perform Operation on (whatever is represented by) Culprit that is of the given PermissionType (in fact, the ISO Standard is confusing and vague about these terms' meaning).
representation_error/1A representation error indicates a limitation of the implementation.
resource_error/1A goal cannot be completed due to lack of resources.
syntax_error/1A text has invalid syntax.
type_error/2Tell the user that Culprit is not of the expected ValidType.
uninstantiation_error/1An argument is over-instantiated.

F.2.17 library(fastrw)

fast_read/1The next term is read from current standard input and is unified with Term.
fast_write/1Output Term in a way that fast_read/1 and fast_read/2 will be able to read it back.
fast_write_to_string/3Perform a fast-write to the difference-slist String\Tail.

F.2.18 library(explain)

explain/1Give an explanation on Term.
explain/2True when Explanation is an explanation of Term.

F.2.19 library(help)

apropos/1Print objects from the manual whose name or summary match with Query.
help/0Show help for What.
help/1Show help for What.
show_html_hook/1Hook called to display the extracted HTML document.

F.2.20 library(gensym)

gensym/2Generate <Base>1, <Base>2, etc atoms on each subsequent call.
reset_gensym/0Reset gensym for all registered keys.
reset_gensym/1Restart generation of identifiers from Base at <Base>1.

F.2.21 library(heaps)

add_to_heap/4Adds Key with priority Priority to Heap0, constructing a new heap in Heap.
delete_from_heap/4Deletes Key from Heap0, leaving its priority in Priority and the resulting data structure in Heap.
empty_heap/1True if Heap is an empty heap.
get_from_heap/4Retrieves the minimum-priority pair Priority-Key from Heap0.
heap_size/2Determines the number of elements in Heap.
heap_to_list/2Constructs a list List of Priority-Element terms, ordered by (ascending) priority.
is_heap/1Returns true if X is a heap.
list_to_heap/2If List is a list of Priority-Element terms, constructs a heap out of List.
merge_heaps/3Merge the two heaps Heap0 and Heap1 in Heap.
min_of_heap/3Unifies Key with the minimum-priority element of Heap and Priority with its priority value.
min_of_heap/5Gets the two minimum-priority elements from Heap.
singleton_heap/3True if Heap is a heap with the single element Priority-Key.

F.2.22 library(increval)

incr_directly_depends/2True if Goal1 depends on Goal2 in the IDG.
incr_invalid_subgoals/1List is a sorted list (set) of the incremental subgoals that are currently invalid.
incr_invalidate_call/1This is the XSB name, but the manual says incr_invalidate_calls/1 and the comment with the code suggests this is misnamed.
incr_invalidate_calls/1Invalidate all tables for subgoals of Goal as well as tables that are affected by these.
incr_is_invalid/1True when Subgoal's table is marked as invalid.
incr_propagate_calls/1Activate the monotonic answer propagation similarly to when a new fact is asserted for a monotonic dynamic predicate.
incr_table_update/0Updated all invalid tables.
incr_trans_depends/2True for each pair in the transitive closure of incr_directly_depends(G1, G2).
is_incremental_subgoal/1This predicate non-deterministically unifies Subgoal with incrementally tabled subgoals that are currently table entries.

F.2.23 library(intercept)

intercept/3Run Goal as call/1.
intercept/4Similar to intercept/3, but the copy of Handler is called as call(Copy,Arg), which allows passing large context arguments or arguments subject to unification or _destructive assignment_.
intercept_all/4True when List contains all instances of Template that have been sent using send_signal/1 where the argument unifies with Ball.
nb_intercept_all/4As intercept_all/4, but backtracing inside Goal does not reset List.
send_signal/1If this predicate is called from a sub-goal of intercept/3, execute the associated _Handler_ of the intercept/3 environment.
send_silent_signal/1As send_signal/1, but succeed silently if there is no matching intercept environment.

F.2.24 library(iostream)

close_any/1Execute the‘Close` closure returned by open_any/5.
open_any/5Establish a stream from Specification that should be closed using Close, which can either be called or passed to close_any/1.
open_hook/6Open Spec in Mode, producing Stream.

F.2.25 library(listing)

listing/0Lists all predicates defined in the calling module.
listing/1List matching clauses.
listing/2List matching clauses.
portray_clause/1Portray‘Clause' on the current output stream.
portray_clause/2Portray‘Clause' on the current output stream.
portray_clause/3Portray‘Clause' on the current output stream.

F.2.26 library(lists)

append/2Concatenate a list of lists.
append/3List1AndList2 is the concatenation of List1 and List2.
clumped/2Pairs is a list of‘Item-Count` pairs that represents the _run length encoding_ of Items.
delete/3Delete matching elements from a list.
flatten/2Is true if FlatList is a non-nested version of NestedList.
intersection/3True if Set3 unifies with the intersection of Set1 and Set2.
is_set/1True if Set is a proper list without duplicates.
last/2Succeeds when Last is the last element of List.
list_to_set/2True when Set has the same elements as List in the same order.
max_list/2True if Max is the largest number in List.
max_member/2True when Max is the largest member in the standard order of terms.
max_member/3True when Max is the largest member according to Pred, which must be a 2-argument callable that behaves like (@=<)/2.
member/2True if Elem is a member of List.
min_list/2True if Min is the smallest number in List.
min_member/2True when Min is the smallest member in the standard order of terms.
min_member/3True when Min is the smallest member according to Pred, which must be a 2-argument callable that behaves like (@=<)/2.
nextto/3True if Y directly follows X in List.
nth0/3True when Elem is the Index'th element of List.
nth0/4Select/insert element at index.
nth1/3Is true when Elem is the Index'th element of List.
nth1/4As nth0/4, but counting starts at 1.
numlist/3List is a list [Low, Low+1, ... High].
permutation/2True when Xs is a permutation of Ys.
prefix/2True iff Part is a leading substring of Whole.
proper_length/2True when Length is the number of elements in the proper list List.
reverse/2Is true when the elements of List2 are in reverse order compared to List1.
same_length/2Is true when List1 and List2 are lists with the same number of elements.
select/3Is true when List1, with Elem removed, results in List2.
select/4Select from two lists at the same position.
selectchk/3Semi-deterministic removal of first element in List that unifies with Elem.
selectchk/4Semi-deterministic version of select/4.
subseq/3Is true when SubList contains a subset of the elements of List in the same order and Complement contains all elements of List not in SubList, also in the order they appear in List.
subset/2True if all elements of SubSet belong to Set as well.
subtract/3Delete all elements in Delete from Set.
sum_list/2Sum is the result of adding all numbers in List.
union/3True if Set3 unifies with the union of the lists Set1 and Set2.

F.2.27 library(macros)

expand_macros/5Perform macro expansion on TermIn with layout PosIn to produce TermOut with layout PosOut.
include_macros/3Include macros from another module.
macro_position/1True when Position is the position of the macro.

F.2.28 library(main)

argv_options/3Parse command line arguments.
argv_options/4As argv_options/3 in __guided__ mode, Currently this version allows parsing argument options throwing an exception rather than calling halt/1 by passing an empty list to ParseOptions.
argv_usage/1Use print_message/2 to print a usage message at Level.
cli_debug_opt_help/2Implements opt_type/3, opt_help/2 and opt_meta/2 for debug arguments.
cli_debug_opt_meta/2Implements opt_type/3, opt_help/2 and opt_meta/2 for debug arguments.
cli_debug_opt_type/3Implements opt_type/3, opt_help/2 and opt_meta/2 for debug arguments.
cli_enable_development_system/0Re-enable the development environment.
cli_parse_debug_options/2Parse certain commandline options for debugging and development purposes.
main/0Call main/1 using the passed command-line arguments.

F.2.29 library(occurs)

contains_term/2Succeeds if Sub is contained in Term (=, deterministically).
contains_var/2Succeeds if Sub is contained in Term (==, deterministically).
free_of_term/2Succeeds of Sub does not unify to any subterm of Term.
free_of_var/2Succeeds of Sub is not equal (==) to any subterm of Term.
occurrences_of_term/3Count the number of SubTerms in Term that _unify_ with SubTerm.
occurrences_of_var/3Count the number of SubTerms in Term that are _equal_ to SubTerm.
sub_term/2Generates (on backtracking) all subterms of Term.
sub_term_shared_variables/3If Sub is a sub term of Term, Vars is bound to the list of variables in Sub that also appear outside Sub in Term.
sub_var/2Generates (on backtracking) all subterms (==) of Term.

F.2.30 library(option)

dict_options/2Convert between an option list and a dictionary.
merge_options/3Merge two option lists.
meta_options/3Perform meta-expansion on options that are module-sensitive.
option/2Get an Option from OptionList.
option/3Get an Option from OptionList.
select_option/3Get and remove Option from an option list.
select_option/4Get and remove Option with default value.

F.2.31 library(optparse)

opt_arguments/3Extract commandline options according to a specification.
opt_help/2True when Help is a help string synthesized from OptsSpec.
opt_parse/4Equivalent to opt_parse(OptsSpec, ApplArgs, Opts, PositionalArgs, []).
opt_parse/5Parse the arguments Args (as list of atoms) according to OptsSpec.
parse_type/3Hook to parse option text Codes to an object of type Type.

F.2.32 library(ordsets)

is_ordset/1True if Term is an ordered set.
list_to_ord_set/2Transform a list into an ordered set.
ord_add_element/3Insert an element into the set.
ord_del_element/3Delete an element from an ordered set.
ord_disjoint/2True if Set1 and Set2 have no common elements.
ord_empty/1True when List is the empty ordered set.
ord_intersect/2True if both ordered sets have a non-empty intersection.
ord_intersect/3Intersection holds the common elements of Set1 and Set2.
ord_intersection/2Intersection of a powerset.
ord_intersection/3Intersection holds the common elements of Set1 and Set2.
ord_intersection/4Intersection and difference between two ordered sets.
ord_memberchk/2True if Element is a member of OrdSet, compared using ==.
ord_selectchk/3Selectchk/3, specialised for ordered sets.
ord_seteq/2True if Set1 and Set2 have the same elements.
ord_subset/2Is true if all elements of Sub are in Super.
ord_subtract/3Diff is the set holding all elements of InOSet that are not in NotInOSet.
ord_symdiff/3Is true when Difference is the symmetric difference of Set1 and Set2.
ord_union/2True if Union is the union of all elements in the superset SetOfSets.
ord_union/3Union is the union of Set1 and Set2.
ord_union/4True iff ord_union(Set1, Set2, Union) and ord_subtract(Set2, Set1, New).

F.2.33 library(persistency)

current_persistent_predicate/1True if PI is a predicate that provides access to the persistent database DB.
db_assert/1Assert Term into the database and record it for persistency.
db_attach/2Use File as persistent database for the calling module.
db_attached/1True if the context module attached to the persistent database File.
db_detach/0Detach persistency from the calling module and delete all persistent clauses from the Prolog database.
db_retract/1Retract terms from the database one-by-one.
db_retractall/1Retract all matching facts and do the same in the database.
db_sync/1Synchronise database with the associated file.
db_sync_all/1Sync all registered databases.
persistent/1Declare dynamic database terms.

F.2.34 library(portraytext)

is_text_code/1Multifile hook that can be used to extend the set of character codes that is recognised as likely text.
portray_text/1Switch portraying on or off.
set_portray_text/2Set options for portraying.
set_portray_text/3Set options for portraying.

F.2.35 library(predicate_options)

assert_predicate_options/4As predicate_options(:PI, +Arg, +Options).
check_predicate_option/3Verify predicate options at runtime.
check_predicate_options/0Analyse loaded program for erroneous options.
current_option_arg/2True when Arg of PI processes predicate options.
current_predicate_option/3True when Arg of PI processes Option.
current_predicate_options/3True when Options is the current active option declaration for PI on Arg.
derive_predicate_options/0Derive new predicate option declarations.
derived_predicate_options/1Derive predicate option declarations for a module.
derived_predicate_options/3Derive option arguments using static analysis.
predicate_options/3Declare that the predicate PI processes options on Arg.
retractall_predicate_options/0Remove all dynamically (derived) predicate options.

F.2.36 library(prologdebug)

debugging/0Report current status of the debugger.
debugging_hook/0Multifile hook that is called as forall(debugging_hook, true) and that may be used to extend the information printed from other debugging libraries.
nospy/1Set/clear spy-points.
nospyall/0Set/clear spy-points.
notrap/1Install a trap on error(Formal, Context) exceptions that unify.
spy/1Set/clear spy-points.
trap/1Install a trap on error(Formal, Context) exceptions that unify.
trap_alias/2Define short hands for commonly used exceptions.

F.2.37 library(prologjiti)

jiti_list/0List the JITI (Just In Time Indexes) of selected predicates.
jiti_list/1List the JITI (Just In Time Indexes) of selected predicates.

F.2.38 library(prologpack)

atom_version/2Translate between atomic version representation and term representation.
pack_attach/2Attach a single package in Dir.
pack_info/1Print more detailed information about Pack.
pack_install/1Install a package.
pack_install/2Install package Name.
pack_list/1Query package server and installed packages and display results.
pack_list_installed/0List currently installed packages.
pack_property/2True when Property is a property of an installed Pack.
pack_rebuild/0Rebuild foreign components of all packages.
pack_rebuild/1Rebuild possible foreign components of Pack.
pack_remove/1Remove the indicated package.
pack_search/1Query package server and installed packages and display results.
pack_upgrade/1Try to upgrade the package Pack.
pack_url_file/2True if File is a unique id for the referenced pack and version.
ssl_verify/5Currently we accept all certificates.

F.2.39 library(prologtrace)

list_tracing/0List predicates we are currently tracing.
notraceall/0Remove all trace points.
trace/1Print passes through _ports_ of specified predicates.
trace/2Print passes through _ports_ of specified predicates.
tracing/2True if Spec is traced using Ports.

F.2.40 library(prologxref)

prolog:called_by/2(hook) Extend cross-referencer
xref_built_in/1Examine defined built-ins
xref_called/3Examine called predicates
xref_clean/1Remove analysis of source
xref_current_source/1Examine cross-referenced sources
xref_defined/3Examine defined predicates
xref_exported/2Examine exported predicates
xref_module/2Module defined by source
xref_source/1Cross-reference analysis of source

F.2.41 library(pairs)

group_pairs_by_key/2Group values with equivalent (==/2) consecutive keys.
map_list_to_pairs/3Create a Key-Value list by mapping each element of List.
pairs_keys/2Remove the values from a list of Key-Value pairs.
pairs_keys_values/3True if Keys holds the keys of Pairs and Values the values.
pairs_values/2Remove the keys from a list of Key-Value pairs.
transpose_pairs/2Swap Key-Value to Value-Key.

F.2.42 library(pio)

F.2.42.1 library(pure_input)

phrase_from_file/2Process the content of File using the DCG rule Grammar.
phrase_from_file/3As phrase_from_file/2, providing additional Options.
phrase_from_stream/2Run Grammer against the character codes on Stream.
stream_to_lazy_list/2Create a lazy list representing the character codes in Stream.
lazy_list_character_count//1True when CharCount is the current character count in the Lazy list.
lazy_list_location//1Determine current (error) location in a lazy list.
syntax_error//1Throw the syntax error Error at the current location of the input.

F.2.43 library(random)

getrand/1Query/set the state of the random generator.
maybe/0Succeed/fail with equal probability (variant of maybe/1).
maybe/1Succeed with probability P, fail with probability 1-P.
maybe/2Succeed with probability K/N (variant of maybe/1).
random/1Binds R to a new random float in the _open_ interval (0.0,1.0).
random/3Generate a random integer or float in a range.
random_between/3Binds R to a random integer in [L,U] (i.e., including both L and U).
random_member/2X is a random member of List.
random_numlist/4Unify List with an ascending list of integers between L and U (inclusive).
random_perm2/4Does X=A,Y=B or X=B,Y=A with equal probability.
random_permutation/2Permutation is a random permutation of List.
random_select/3Randomly select or insert an element.
random_subseq/3Selects a random subsequence Subseq of List, with Complement containing all elements of List that were not selected.
randseq/3S is a list of K unique random integers in the range 1..N.
randset/3S is a sorted list of K unique random integers in the range 1..N.
setrand/1Query/set the state of the random generator.

F.2.44 library(rbtrees)

is_rbtree/1True if Term is a valid Red-Black tree.
list_to_rbtree/2Tree is the red-black tree corresponding to the mapping in List, which should be a list of Key-Value pairs.
ord_list_to_rbtree/2Tree is the red-black tree corresponding to the mapping in list List, which should be a list of Key-Value pairs.
rb_apply/4If the value associated with key Key is Val0 in Tree, and if call(G,Val0,ValF) holds, then NewTree differs from Tree only in that Key is associated with value ValF in tree NewTree.
rb_clone/3‘Clone' the red-back tree TreeIn into a new tree TreeOut with the same keys as the original but with all values set to unbound values.
rb_del_max/4Delete the largest element from the tree Tree, returning the key Key, the value Val associated with the key and a new tree NewTree.
rb_del_min/4Delete the least element from the tree Tree, returning the key Key, the value Val associated with the key and a new tree NewTree.
rb_delete/3Delete element with key Key from the tree Tree, returning the value Val associated with the key and a new tree NewTree.
rb_delete/4Same as rb_delete(Tree, Key, NewTree), but also unifies Val with the value associated with Key in Tree.
rb_empty/1Succeeds if Tree is an empty Red-Black tree.
rb_fold/4Fold the given predicate over all the key-value pairs in Tree, starting with initial state State0 and returning the final state State.
rb_in/3True when Key-Value is a key-value pair in red-black tree Tree.
rb_insert/4Add an element with key Key and Value to the tree Tree creating a new red-black tree NewTree.
rb_insert_new/4Add a new element with key Key and Value to the tree Tree creating a new red-black tree NewTree.
rb_keys/2Keys is unified with an ordered list of all keys in the Red-Black tree Tree.
rb_lookup/3True when Value is associated with Key in the Red-Black tree Tree.
rb_map/2True if call(Goal, Value) is true for all nodes in T.
rb_map/3For all nodes Key in the tree Tree, if the value associated with key Key is Val0 in tree Tree, and if call(G,Val0,ValF) holds, then the value associated with Key in NewTree is ValF.
rb_max/3Key is the maximal key in Tree, and is associated with Val.
rb_min/3Key is the minimum key in Tree, and is associated with Val.
rb_new/1Create a new Red-Black tree Tree.
rb_next/4Next is the next element after Key in Tree, and is associated with Val.
rb_partial_map/4For all nodes Key in Keys, if the value associated with key Key is Val0 in tree Tree, and if call(G,Val0,ValF) holds, then the value associated with Key in NewTree is ValF, otherwise it is the value associated with the key in Tree.
rb_previous/4Previous is the previous element after Key in Tree, and is associated with Val.
rb_size/2Size is the number of elements in Tree.
rb_update/4Tree NewTree is tree Tree, but with value for Key associated with NewVal.
rb_update/5Same as =|rb_update(Tree, Key, NewVal, NewTree)|= but also unifies OldVal with the value associated with Key in Tree.
rb_visit/2Pairs is an infix visit of tree Tree, where each element of Pairs is of the form Key-Value.

F.2.45 library(readutil)

read_file_to_codes/3Read the file Spec into a list of Codes.
read_file_to_string/3Read the file Spec into a the string String.
read_file_to_terms/3Read the file Spec into a list of terms.
read_line_to_codes/2Read the next line of input from Stream.
read_line_to_codes/3Difference-list version to read an input line to a list of character codes.
read_line_to_string/2Read the next line from Stream into String.
read_stream_to_codes/2Read input from Stream to a list of character codes.
read_stream_to_codes/3Read input from Stream to a list of character codes.

F.2.46 library(record)

record/1Define named fields in a term

F.2.47 library(registry)

This library is only available on Windows systems.

registry_get_key/2Get principal value of key
registry_get_key/3Get associated value of key
registry_set_key/2Set principal value of key
registry_set_key/3Set associated value of key
registry_delete_key/1Remove a key
shell_register_file_type/4Register a file-type
shell_register_dde/6Register DDE action
shell_register_prolog/1Register Prolog

F.2.48 library(rwlocks)

with_rwlock/3Run Goal, synchronized with LockId in ModeSpec.
with_rwlock/4Run Goal, synchronized with LockId in ModeSpec.

F.2.49 library(settings)

convert_setting_text/3Converts from textual form to Prolog Value.
current_setting/1True if Setting is a currently defined setting.
env/2Evaluate environment variables on behalf of arithmetic expressions.
env/3Evaluate environment variables on behalf of arithmetic expressions.
list_settings/0List settings to =current_output=.
list_settings/1List settings to =current_output=.
load_settings/1Load local settings from File.
load_settings/2Load local settings from File.
restore_setting/1Restore the value of setting Name to its default.
save_settings/0Save modified settings to File.
save_settings/1Save modified settings to File.
set_setting/2Change a setting.
set_setting_default/2Change the default for a setting.
setting/2True when Name is a currently defined setting with Value.
setting/4Define a setting.
setting_property/2Query currently defined settings.

F.2.50 library(simplex)

assignment/2Solve assignment problem
constraint/3Add linear constraint to state
constraint/4Add named linear constraint to state
constraint_add/4Extend a named constraint
gen_state/1Create empty linear program
maximize/3Maximize objective function in to linear constraints
minimize/3Minimize objective function in to linear constraints
objective/2Fetch value of objective function
shadow_price/3Fetch shadow price in solved state
transportation/4Solve transportation problem
variable_value/3Fetch value of variable in solved state

F.2.51 library(statistics)

call_time/2Call Goal as call/1, unifying Time with a dict that provides information on the resource usage.
call_time/3Call Goal as call/1, unifying Time with a dict that provides information on the resource usage.
statistics/0Print information about resource usage using print_message/2.
statistics/1Stats is a dict representing the same information as statistics/0.
thread_statistics/2Obtain statistical information about a single thread.
time/1Execute Goal, reporting statistics to the user.

F.2.52 library(terms)

foldsubterms/4The predicate foldsubterms/5 calls call(Goal4, SubTerm1, SubTerm2, StateIn, StateOut) for each subterm, including variables, in Term1.
foldsubterms/5The predicate foldsubterms/5 calls call(Goal4, SubTerm1, SubTerm2, StateIn, StateOut) for each subterm, including variables, in Term1.
mapargs/3Term1 and Term2 have the same functor (name/arity) and for each matching pair of arguments call(Goal, A1, A2) is true.
mapsubterms/3Recursively map sub terms of Term1 into subterms of Term2 for every pair for which call(Goal, ST1, ST2) succeeds.
mapsubterms_var/3Recursively map sub terms of Term1 into subterms of Term2 for every pair for which call(Goal, ST1, ST2) succeeds.
same_functor/2True when Term1 and Term2 are terms that have the same functor (Name/Arity).
same_functor/3True when Term1 and Term2 are terms that have the same functor (Name/Arity).
same_functor/4True when Term1 and Term2 are terms that have the same functor (Name/Arity).
subsumes/2True if Generic is unified to Specific without changing Specific.
subsumes_chk/2True if Generic can be made equivalent to Specific without changing Specific.
term_factorized/3Is true when Skeleton is Term where all subterms that appear multiple times are replaced by a variable and Substitution is a list of Var=Value that provides the subterm at the location Var.
term_size/2True if Size is the size in _cells_ occupied by Term on the global (term) stack.
term_subsumer/3General is the most specific term that is a generalisation of Special1 and Special2.
variant/2Same as SWI-Prolog =|Term1 =@= Term2|=.

F.2.53 library(ugraphs)

add_edges/3Unify NewGraph with a new graph obtained by adding the list of Edges to Graph.
add_vertices/3Unify NewGraph with a new graph obtained by adding the list of Vertices to Graph.
complement/2UGraphOut is a ugraph with an edge between all vertices that are _not_ connected in UGraphIn and all edges from UGraphIn removed.
compose/3Compose NewGraph by connecting the _drains_ of LeftGraph to the _sources_ of RightGraph.
connect_ugraph/3Adds Start as an additional vertex that is connected to all vertices in UGraphIn.
del_edges/3Unify NewGraph with a new graph obtained by removing the list of Edges from Graph.
del_vertices/3Unify NewGraph with a new graph obtained by deleting the list of Vertices and all the edges that start from or go to a vertex in Vertices to the Graph.
edges/2Unify Edges with all edges appearing in Graph.
neighbors/3Neigbours is a sorted list of the neighbours of Vertex in Graph.
neighbours/3Neigbours is a sorted list of the neighbours of Vertex in Graph.
reachable/3True when Vertices is an ordered set of vertices reachable in UGraph, including Vertex.
top_sort/2Sort vertices topologically.
transitive_closure/2Generate the graph Closure as the transitive closure of Graph.
transpose_ugraph/2Unify NewGraph with a new graph obtained from Graph by replacing all edges of the form V1-V2 by edges of the form V2-V1.
ugraph_layers/2Sort vertices topologically.
ugraph_union/3NewGraph is the union of Graph1 and Graph2.
vertices/2Unify Vertices with all vertices appearing in Graph.
vertices_edges_to_ugraph/3Create a UGraph from Vertices and edges.
vertices_edges_to_ugraph/3Create unweighted graph
vertices/2Find vertices in graph
edges/2Find edges in graph
add_vertices/3Add vertices to graph
del_vertices/3Delete vertices from graph
add_edges/3Add edges to graph
del_edges/3Delete edges from graph
transpose_ugraph/2Invert the direction of all edges
neighbors/3Find neighbors of vertice
neighbours/3Find neighbors of vertice
complement/2Inverse presense of edges
compose/3
top_sort/2Sort graph topologically
top_sort/3Sort graph topologically
transitive_closure/2Create transitive closure of graph
reachable/3Find all reachable vertices
ugraph_union/3Union of two graphs

F.2.54 library(url)

file_name_to_url/2Translate between a filename and a file:// URL.
global_url/3Translate a possibly relative URL into an absolute one.
http_location/2Construct or analyze an HTTP location.
is_absolute_url/1True if URL is an absolute URL.
parse_url/2Construct or analyse a URL.
parse_url/3Similar to parse_url/2 for relative URLs.
parse_url_search/2Construct or analyze an HTTP search specification.
set_url_encoding/2Query and set the encoding for URLs.
url_iri/2Convert between a URL, encoding in US-ASCII and an IRI.
www_form_encode/2En/decode to/from application/x-www-form-encoded.

F.2.55 library(www_browser)

expand_url_path/2Expand URL specifications similar to absolute_file_name/3.
known_browser/2True if browser FileBaseName has a remote protocol compatible to Compatible.
www_open_url/1Open URL in running version of the users' browser or start a new browser.

F.2.56 library(solution_sequences)

call_nth/2True when Goal succeeded for the Nth time.
distinct/1True if Goal is true and no previous solution of Goal bound Witness to the same value.
distinct/2True if Goal is true and no previous solution of Goal bound Witness to the same value.
group_by/4Group bindings of Template that have the same value for By.
limit/2Limit the number of solutions.
offset/2Ignore the first Count solutions.
order_by/2Order solutions according to Spec.
reduced/1Similar to distinct/1, but does not guarantee unique results in return for using a limited amount of memory.
reduced/3Similar to distinct/1, but does not guarantee unique results in return for using a limited amount of memory.

F.2.57 library(thread)

call_in_thread/2Run Goal as an interrupt in the context of Thread.
concurrent/3Run Goals in parallel using N threads.
concurrent_and/2Concurrent version of‘(Generator,Test)`.
concurrent_and/3Concurrent version of‘(Generator,Test)`.
concurrent_forall/2True when Action is true for all solutions of Generate.
concurrent_forall/3True when Action is true for all solutions of Generate.
concurrent_maplist/2Concurrent version of maplist/2.
concurrent_maplist/3Concurrent version of maplist/2.
concurrent_maplist/4Concurrent version of maplist/2.
first_solution/3Try alternative solvers concurrently, returning the first answer.

F.2.58 library(thread_pool)

create_pool/1Hook to create a thread pool lazily.
current_thread_pool/1True if Name refers to a defined thread pool.
thread_create_in_pool/4Create a thread in Pool.
thread_pool_create/3Create a pool of threads.
thread_pool_destroy/1Destroy the thread pool named Name.
thread_pool_property/2True if Property is a property of thread pool Name.
worker_exitted/3It is possible that’__thread_pool_manager' no longer exists while closing down the process because the manager was killed before the worker.

F.2.59 library(varnumbers)

max_var_number/3True when Max is the max of Start and the highest numbered $VAR(N) term.
numbervars/1Number variables in Term using $VAR(N).
varnumbers/2Inverse of numbervars/1.
varnumbers/3Inverse of numbervars/3.
varnumbers_names/3If Term is a term with numbered and named variables using the reserved term’$VAR'(X), Copy is a copy of Term where each’$VAR'(X) is consistently replaced by a fresh variable and Bindings is a list‘X = Var`, relating the‘X` terms with the variable it is mapped to.

F.2.60 library(yall)

//2Shorthand for‘Free/[]>>Lambda`.
//3Shorthand for‘Free/[]>>Lambda`.
//4Shorthand for‘Free/[]>>Lambda`.
//5Shorthand for‘Free/[]>>Lambda`.
//6Shorthand for‘Free/[]>>Lambda`.
//7Shorthand for‘Free/[]>>Lambda`.
//8Shorthand for‘Free/[]>>Lambda`.
//9Shorthand for‘Free/[]>>Lambda`.
>>/2Calls a copy of Lambda.
>>/3Calls a copy of Lambda.
>>/4Calls a copy of Lambda.
>>/5Calls a copy of Lambda.
>>/6Calls a copy of Lambda.
>>/7Calls a copy of Lambda.
>>/8Calls a copy of Lambda.
>>/9Calls a copy of Lambda.
is_lambda/1True if Term is a valid Lambda expression.
lambda_calls/2Goal is the goal called if call/N is applied to LambdaExpression, where ExtraArgs are the additional arguments to call/N.
lambda_calls/3Goal is the goal called if call/N is applied to LambdaExpression, where ExtraArgs are the additional arguments to call/N.