[not loaded]All predicatesShow sourcesyspred.pl

Source map_bits(:Pred, +Modify, +OldBits, -NewBits)[private]
Source style_check(+Spec) is nondet
Source flag(+Name, -Old, +New) is det
True when Old is the current value associated with the flag Name and New has become the new value.
Source source_file(-File) is nondet
source_file(+File) is semidet
True if File is loaded into Prolog. If File is unbound it is bound to the canonical name for it. If File is bound it succeeds if the canonical name as defined by absolute_file_name/2 is known as a loaded filename.

Note that Time = 0 is used by PlDoc and other code that needs to create a file record without being interested in the time.

Source source_file(+Head, -File) is semidet
source_file(?Head, ?File) is nondet
True when Head is a predicate owned by File.
Source source_file_property(?File, ?Property) is nondet
True if Property is a property of the loaded source-file File.
Source canonical_source_file(+Spec, -File) is semidet[private]
File is the canonical representation of the source-file Spec.
Source exists_source(+Source) is semidet
Source exists_source(+Source, -Path) is semidet
True if Source (a term valid for load_files/2) exists. Fails without error if this is not the case. The predicate is intended to be used with :- if, as in the example below. See also source_exports/2.
:- if(exists_source(library(error))).
:- use_module_library(error).
:- endif.
Source prolog_load_context(+Key, -Value)
Provides context information for term_expansion and directives. Note that only the line-number info is valid for the '$stream_position'. Largely Quintus compatible.
Source unload_file(+File) is det
Remove all traces of loading file.
Source use_foreign_library(+FileSpec) is det
Source use_foreign_library(+FileSpec, +Entry:atom) is det
Load and install a foreign library as load_foreign_library/1,2 and register the installation using initialization/2 with the option now. This is similar to using:
:- initialization(load_foreign_library(foreign(mylib))).

but using the initialization/1 wrapper causes the library to be loaded after loading of the file in which it appears is completed, while use_foreign_library/1 loads the library immediately. I.e. the difference is only relevant if the remainder of the file uses functionality of the C-library.

Source current_foreign_library(?File, -Public)[private]
Query currently loaded shared libraries.
Source stream_position_data(?Field, +Pos, ?Date)
Extract values from stream position objects. '$stream_position' is of the format '$stream_position'(Byte, Char, Line, LinePos)
Source call_with_depth_limit(:Goal, +DepthLimit, -Result)
Try to proof Goal, but fail on any branch exceeding the indicated depth-limit. Unify Result with the maximum-reached limit on success, depth_limit_exceeded if the limit was exceeded and fails otherwise.
Source call_with_inference_limit(:Goal, +InferenceLimit, -Result)
Equivalent to call(Goal), but poses a limit on the number of inferences. If this limit is reached, Result is unified with inference_limit_exceeded, otherwise Result is unified with ! if Goal succeeded without a choicepoint and true otherwise.

Note that we perform calls in system to avoid auto-importing, which makes raiseInferenceLimitException() fail to recognise that the exception happens in the overhead.

Source predicate_property(?Predicate, ?Property) is nondet
True when Property is a property of Predicate.
Source property_predicate(+Property, ?Pred)[private]
First handle the special cases that are not about querying normally defined predicates: undefined, visible and autoload, followed by the generic case.
Source define_or_generate(+Head) is semidet[private]
define_or_generate(-Head) is nondet[private]
If the predicate is known, try to resolve it. Otherwise generate the known predicate, but do not try to (auto)load the predicate.
Source visible_predicate(:Head) is nondet[private]
True when Head can be called without raising an existence error. This implies it is defined, can be inherited from a default module or can be autoloaded.
Source clause_property(+ClauseRef, ?Property) is nondet
Provide information on individual clauses. Defined properties are:
line_count(-Line)
Line from which the clause is loaded.
file(-File)
File from which the clause is loaded.
source(-File)
File that `owns' the clause: reloading this file wipes the clause.
fact
Clause has body true.
erased
Clause was erased.
predicate(:PI)
Predicate indicator of the predicate this clause belongs to. Can be used to find the predicate of erased clauses.
module(-M)
Module context in which the clause was compiled.
Source dynamic(:Predicates, +Options) is det
Define a predicate as dynamic with optionally additional properties. Defined options are:
Source current_module(?Module) is nondet
True if Module is a currently defined module.
Source module_property(?Module, ?Property) is nondet
True if Property is a property of Module. Defined properties are:
file(File)
Module is loaded from File.
line_count(Count)
The module declaration is on line Count of File.
exports(ListOfPredicateIndicators)
The module exports ListOfPredicateIndicators
exported_operators(ListOfOp3)
The module exports the operators ListOfOp3.
Source module(+Module) is det
Set the module that is associated to the toplevel to Module.
Source working_directory(-Old, +New)
True when Old is the current working directory and the working directory has been updated to New.
Source current_trie(?Trie) is nondet
True if Trie is the handle of an existing trie.
Source trie_property(?Trie, ?Property)
True when Property is a property of Trie. Defined properties are:
value_count(Count)
Number of terms in the trie.
node_count(Count)
Number of nodes in the trie.
size(Bytes)
Number of bytes needed to store the trie.
hashed(Count)
Number of hashed nodes.
compiled_size(Bytes)
Size of the compiled representation (if the trie is compiled)
lookup_count(Count)
Number of data lookups on the trie
gen_call_count(Count)
Number of trie_gen/2 calls on this trie

Incremental tabling statistics:

invalidated(Count)
Number of times the trie was inivalidated
reevaluated(Count)
Number of times the trie was re-evaluated

Shared tabling statistics:

deadlock(Count)
Number of times the table was involved in a deadlock
wait(Count)
Number of times a thread had to wait for this table
Source on_signal(+Signal, -OldHandler, :NewHandler) is det
Source current_signal(?Name, ?SignalNumber, :Handler) is nondet
Source absolute_file_name(+Term, -AbsoluteFile)
Source tmp_file_stream(-File, -Stream, +Options) is det
tmp_file_stream(+Encoding, -File, -Stream) is det
Create a temporary file and open it atomically. The second mode is for compatibility reasons.
Source garbage_collect is det
Invoke the garbage collector. The argument of the underlying '$garbage_collect'/1 is the debugging level to use during garbage collection. This only works if the system is compiled with the -DODEBUG cpp flag. Only to simplify maintenance.
Source set_prolog_stack(+Name, +Option) is det
Set a parameter for one of the Prolog stacks.
Source prolog_stack_property(?Stack, ?Property) is nondet
Examine stack properties.
Source rule(:Head, -Rule) is nondet
Source rule(:Head, -Rule, Ref) is nondet
Similar to clause/2,3. but deals with clauses that do not use :- as neck.
Source numbervars(+Term, +StartIndex, -EndIndex) is det
Number all unbound variables in Term using '$VAR'(N), where the first N is StartIndex and EndIndex is unified to the index that will be given to the next variable.
Source term_string(?Term, ?String, +Options)
Parse/write a term from/to a string using Options.
Source thread_create(:Goal, -Id)
Shorthand for thread_create(Goal, Id, []).
Source thread_join(+Id)
Join a thread and raise an error of the thread did not succeed.
Errors
- thread_error(Status), where Status is the result of thread_join/2.
Source sig_block(:Pattern) is det
Block thread signals that unify with Pattern.
Source sig_unblock(:Pattern) is det
Remove any signal block that is more specific than Pattern.
Source set_prolog_gc_thread(+Status)
Control the GC thread. Status is one of
false
Disable the separate GC thread, running atom and clause garbage collection in the triggering thread.
true
Enable the separate GC thread. All implicit atom and clause garbage collection is executed by the thread gc.
stop
Stop the gc thread if it is running. The thread is recreated on the next implicit atom or clause garbage collection. Used by fork/1 to avoid forking a multi-threaded application.
Source transaction(:Goal)
Source transaction(:Goal, +Options)
Source transaction(:Goal, :Constraint, +Mutex)
Source snapshot(:Goal)
Wrappers to guarantee clean Module:Goal terms.
Source undo(:Goal)
Schedule Goal to be called when backtracking takes us back to before this call.
Source $wrap_predicate(:Head, +Name, -Closure, -Wrapped, :Body) is det
Would be nicer to have this from library(prolog_wrap), but we need it for tabling, so it must be a system predicate.

Undocumented predicates

The following predicates are exported, but not or incorrectly documented.

Source $defined_predicate(Arg1)
Source current_predicate(Arg1, Arg2)
Source atom_prefix(Arg1, Arg2)
Source format(Arg1)
Source visible(Arg1)
Source rule(Arg1, Arg2, Arg3)
Source exists_source(Arg1, Arg2)
Source leash(Arg1)
Source dwim_match(Arg1, Arg2)
Source use_foreign_library(Arg1, Arg2)
Source $predicate_property(Arg1, Arg2)
Source transaction(Arg1, Arg2, Arg3)
Source snapshot(Arg1)
Source shell(Arg1)
Source transaction(Arg1, Arg2)