[not loaded]init.pl
- dynamic +Spec is det[private]
- multifile +Spec is det[private]
- module_transparent +Spec is det[private]
- discontiguous +Spec is det[private]
- volatile +Spec is det[private]
- thread_local +Spec is det[private]
- noprofile(+Spec) is det[private]
- public +Spec is det[private]
- non_terminal(+Spec) is det[private]
- Predicate versions of standard directives that set predicate attributes. These predicates bail out with an error on the first failure (typically permission errors).
- $iso(+Spec) is det[private]
- Set the ISO flag. This defines that the predicate cannot be redefined inside a module.
- $clausable(+Spec) is det[private]
- Specify that we can run clause/2 on a predicate, even if it is
static. ISO specifies that
public
also plays this role. in SWI,public
means that the predicate can be called, even if we cannot find a reference to it. - $hide(+Spec) is det[private]
- Specify that the predicate cannot be seen in the debugger.
- $set_pattr(+Spec, +Module, +From, +Attr)[private]
- Set predicate attributes. From is one of
pred
ordirective
. - $pattr_directive(+Spec, +Module) is det[private]
- This implements the directive version of dynamic/1, multifile/1, etc. This version catches and prints errors. If the directive specifies multiple predicates, processing after an error continues with the remaining predicates.
- $pi_head(?PI, ?Head)[private]
- $head_name_arity(+Goal, -Name, -Arity)[private]
- $head_name_arity(-Goal, +Name, +Arity)[private]
- $meta_call(:Goal)[private]
- Interpreted meta-call implementation. By default, call/1
compiles its argument into a temporary clause. This realises
better performance if the (complex) goal does a lot of
backtracking because this interpreted version needs to
re-interpret the remainder of the goal after backtracking.
This implementation is used by reset/3 because the continuation cannot be captured if it contains a such a compiled temporary clause.
- call(:Closure, ?A)[private]
- call(:Closure, ?A1, ?A2)[private]
- call(:Closure, ?A1, ?A2, ?A3)[private]
- call(:Closure, ?A1, ?A2, ?A3, ?A4)[private]
- call(:Closure, ?A1, ?A2, ?A3, ?A4, ?A5)[private]
- call(:Closure, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6)[private]
- call(:Closure, ?A1, ?A2, ?A3, ?A4, ?A5, ?A6, ?A7)[private]
- Arity 2..8 is demanded by the ISO standard. Higher arities are supported, but handled by the compiler. This implies they are not backed up by predicates and analyzers thus cannot ask for their properties. Analyzers should hard-code handling of call/2..
- not(:Goal) is semidet[private]
- Pre-ISO version of \+/1. Note that some systems define not/1 as a logically more sound version of \+/1.
- \+ :Goal is semidet[private]
- Predicate version that allows for meta-calling.
- once(:Goal) is semidet[private]
- ISO predicate, acting as
call((Goal, !))
. - ignore(:Goal) is det[private]
- Call Goal, cut choice-points on success and succeed on failure. intended for calling side-effects and proceed on failure.
- false[private]
- Synonym for fail/0, providing a declarative reading.
- catch(:Goal, +Catcher, :Recover)[private]
- ISO compliant exception handling.
- prolog_cut_to(+Choice)[private]
- Cut all choice points after Choice
- reset(:Goal, ?Ball, -Continue)[private]
- Delimited continuation support.
- shift(+Ball)[private]
- Shift control back to the enclosing reset/3
- call_continuation(+Continuation:list)[private]
- Call a continuation as created by shift/1. The continuation is a
list of '$cont$'(Clause, PC, EnvironmentArg, ...) structures. The
predicate '$call_one_tail_body'/1 creates a frame from the
continuation and calls this.
Note that we can technically also push the entire continuation onto the environment and call it. Doing it incrementally as below exploits last-call optimization and therefore possible quadratic expansion of the continuation.
- catch_with_backtrace(:Goal, ?Ball, :Recover)[private]
- As catch/3, but tell library(prolog_stack) to record a backtrace in case of an exception.
- $recover_and_rethrow(:Goal, +Term)[private]
- This goal is used to wrap the catch/3 recover handler if the exception is not supposed to be `catchable'. An example of an uncachable exception is '$aborted', used by abort/0. Note that we cut to ensure that the exception is not delayed forever because the recover handler leaves a choicepoint.
- setup_call_cleanup(:Setup, :Goal, :Cleanup)[private]
- setup_call_catcher_cleanup(:Setup, :Goal, +Catcher, :Cleanup)[private]
- call_cleanup(:Goal, :Cleanup)[private]
- call_cleanup(:Goal, +Catcher, :Cleanup)[private]
- Call Cleanup once after Goal is finished (deterministic success, failure, exception or cut). The call to '$call_cleanup' is translated to I_CALLCLEANUP. This instruction relies on the exact stack layout left by setup_call_catcher_cleanup/4. Also the predicate name is used by the kernel cleanup mechanism and can only be changed together with the kernel.
- initialization(:Goal, +When)[private]
- Register Goal to be executed if a saved state is restored. In
addition, the goal is executed depending on When:
- now
- Execute immediately
- after_load
- Execute after loading the file in which it appears. This is initialization/1.
- restore_state
- Do not execute immediately, but only when restoring the state. Not allowed in a sandboxed environment.
- prepare_state
- Called before saving a state. Can be used to clean the environment (see also volatile/1) or eagerly execute goals that are normally executed lazily.
- program
- Works as
-g goal
goals. - main
- Starts the application. Only last declaration is used.
Note that all goals are executed when a program is restored.
- $run_initialization(?File, +Options) is det[private]
- $run_initialization(?File, +Action, +Options) is det[private]
- Run initialization directives for all files if File is unbound,
or for a specified file. Note that '$run_initialization'/2 is
called from
runInitialization()
in pl-wic.c for .qlf files. The '$run_initialization'/3 is called with Action set toloaded
when called for a QLF file. - $clear_source_admin(+File) is det[private]
- Removes source adminstration related to File
- default_module(+Me, -Super) is multi[private]
- Is true if `Super' is `Me' or a super (auto import) module of `Me'.
- $undefined_procedure(+Module, +Name, +Arity, -Action) is det[private]
- This predicate is called from C on undefined predicates. First allows the user to take care of it using exception/3. Else try to give a DWIM warning. Otherwise fail. C will print an error message.
- $loading(+Library)[private]
- True if the library is being loaded. Just testing that the predicate is defined is not good enough as the file may be partly loaded. Calling use_module/2 at any time has two drawbacks: it queries the filesystem, causing slowdown and it stops libraries being autoloaded from a saved state where the library is already loaded, but the source may not be accessible.
- $confirm(Spec)[private]
- Ask the user to confirm a question. Spec is a term as used for print_message/2.
- $expand_file_search_path(+Spec, -Expanded, +Cond) is nondet[private]
- expand_file_search_path(+Spec, -Expanded) is nondet[private]
- Expand a search path. The system uses depth-first search upto a specified depth. If this depth is exceeded an exception is raised. TBD: bread-first search?
- absolute_file_name(+Term, -AbsoluteFile, +Options) is nondet[private]
- Translate path-specifier into a full path-name. This predicate originates from Quintus was introduced in SWI-Prolog very early and has re-appeared in SICStus 3.9.0, where they changed argument order and added some options. We addopted the SICStus argument order, but still accept the original argument order for compatibility reasons.
- user:prolog_file_type(?Extension, ?Type)[multifile]
- Define type of file based on the extension. This is used by
absolute_file_name/3 and may be used to extend the list of
extensions used for some type.
Note that
qlf
must be last when searching for Prolog files. Otherwise use_module/1 will consider the file as not-loaded because the .qlf file is not the loaded file. Must be fixed elsewhere. - $chk_file(+Spec, +Extensions, +Cond, +UseCache, -FullName)[private]
- File is a specification of a Prolog source file. Return the full path of the file.
- $relative_to(+Condition, +Default, -Dir)[private]
- Determine the directory to work from. This can be specified
explicitely using one or more
relative_to(FileOrDir)
options or implicitely relative to the working directory or current source-file. - $chk_alias_file(+Spec, +Exts, +Cond, +Cache, +CWD, -FullFile) is nondet[private]
- $file_conditions(+Condition, +Path)[private]
- Verify Path satisfies Condition.
- $list_to_set(+List, -Set) is det[private]
- Turn list into a set, keeping the left-most copy of duplicate
elements. Note that library(lists) provides an O(N*
log(N)
) version, but sets of file name extensions should be short enough for this not to matter. - $compilation_level(-Level) is det[private]
- True when Level reflects the nesting in files compiling other files. 0 if no files are being loaded.
- compiling[private]
- Is true if SWI-Prolog is generating a state or qlf file or executes a `call' directive while doing this.
- $load_msg_level(+Action, +NestingLevel, -StartVerbose, -EndVerbose)[private]
- $source_term(+From, -Read, -RLayout, -Term, -TLayout, -Stream, +Options) is nondet[private]
- Read Prolog terms from the input From. Terms are returned on backtracking. Associated resources (i.e., streams) are closed due to setup_call_cleanup/3.
- $term_in_file(+In, -Read, -RLayout, -Term, -TLayout, -Stream, +Parents, +Options) is multi[private]
- True when Term is an expanded term from In. Read is a raw term (before term-expansion). Stream is the actual stream, which starts at In, but may change due to processing included files.
- $add_encoding(+Enc, +Options0, -Options)[private]
- $record_included(+Parents, +File, +Path, +Time, -Message) is det[private]
- Record that we included File into the head of Parents. This is
troublesome when creating a QLF file because this may happen
before we opened the QLF file (and we do not yet know how to
open the file because we do not yet know whether this is a
module file or not).
I think that the only sensible solution is to have a special statement for this, that may appear both inside and outside QLF `parts'.
- $master_file(+File, -MasterFile)[private]
- Find the primary load file from included files.
- ensure_loaded(+FileOrListOfFiles)[private]
- Load specified files, provided they where not loaded before. If the file is a module file import the public predicates into the context module.
- use_module(+FileOrListOfFiles)[private]
- Very similar to ensure_loaded/1, but insists on the loaded file to be a module file. If the file is already imported, but the public predicates are not yet imported into the context module, then do so.
- use_module(+File, +ImportList)[private]
- As use_module/1, but takes only one file argument and imports only the specified predicates rather than all public predicates.
- reexport(+Files)[private]
- As use_module/1, exporting all imported predicates.
- reexport(+File, +ImportList)[private]
- As use_module/1, re-exporting all imported predicates.
- load_files(:File, +Options)[private]
- Common entry for all the consult derivates. File is the raw user specified file specification, possibly tagged with the module.
- $noload(+Condition, +FullFile, +Options) is semidet[private]
- True of FullFile should not be loaded.
- $qlf_file(+Spec, +PlFile, -LoadFile, -Mode, +Options) is det[private]
- Determine how to load the source. LoadFile is the file to be loaded,
Mode is how to load it. Mode is one of
- compile
- Normal source compilation
- qcompile
- Compile from source, creating a QLF file in the process
- qload
- Load from QLF file.
- stream
- Load from a stream. Content can be a source or QLF file.
- $qlf_out_of_date(+PlFile, +QlfFile, -Why) is semidet[private]
- True if the QlfFile file is out-of-date because of Why. This predicate is the negation such that we can return the reason.
- $qlf_auto(+PlFile, +QlfFile, +Options) is semidet[private]
- True if we create QlfFile using qcompile/2. This is determined
by the option
qcompile(QlfMode)
or, if this is not present, by the prolog_flag qcompile. - $load_file(+Spec, +ContextModule, +Options) is det[private]
- Load the file Spec into ContextModule controlled by Options.
This wrapper deals with two cases before proceeding to the real
loader:
- User hooks based on prolog_load_file/2
- The file is already loaded.
- $resolved_source_path(+File, -FullFile, +Options) is semidet[private]
- True when File has already been resolved to an absolute path.
- $resolve_source_path(+File, -FullFile, Options) is det[private]
- Resolve a source file specification to an absolute path. May throw existence and other errors.
- $translated_source(+Old, +New) is det[private]
- Called from loading a QLF state when source files are being renamed.
- $register_resource_file(+FullFile) is det[private]
- If we load a file from a resource we lock it, so we never have to check the modification again.
- $already_loaded(+File, +FullFile, +Module, +Options) is det[private]
- Called if File is already loaded. If this is a module-file, the module must be imported into the context Module. If it is not a module file, it must be reloaded.
- $mt_load_file(+File, +FullFile, +Module, +Options) is det[private]
- Deal with multi-threaded loading of files. The thread that
wishes to load the thread first will do so, while other threads
will wait until the leader finished and than act as if the file
is already loaded.
Synchronisation is handled using a message queue that exists while the file is being loaded. This synchronisation relies on the fact that thread_get_message/1 throws an existence_error if the message queue is destroyed. This is hacky. Events or condition variables would have made a cleaner design.
- $qdo_load_file(+Spec, +FullFile, +ContextModule, +Options) is det[private]
- Switch to qcompile mode if requested by the option '$qlf'(+Out)
- $do_load_file(+Spec, +FullFile, +ContextModule, -Action, +Options) is det[private]
- Perform the actual loading.
- $save_file_scoped_flags(-State) is det[private]
- $restore_file_scoped_flags(-State) is det[private]
- Save/restore flags that are scoped to a compilation unit.
- $import_from_loaded_module(LoadedModule, Module, Options) is det[private]
- Import public predicates from LoadedModule into Module
- $set_verbose_load(+Options, -Old) is det[private]
- Set the
verbose_load
flag according to Options and unify Old with the old value. - $set_sandboxed_load(+Options, -Old) is det[private]
- Update the Prolog flag
sandboxed_load
from Options. Old is unified with the old flag. - $update_autoload_level(+Options, -OldLevel)[private]
- Update the '$autoload_nesting' and return the old value.
- $print_message(+Level, +Term) is det[private]
- As print_message/2, but deal with the fact that the message system might not yet be loaded.
- $consult_file(+Path, +Module, -Action, -LoadedIn, +Options)[private]
- Called from '$do_load_file'/4 using the goal returned by '$consult_goal'/2. This means that the calling conventions must be kept synchronous with '$qload_file'/6.
- $save_lex_state(-LexState, +Options) is det[private]
- $assert_load_context_module(+File, -Module, -Options)[private]
- Record the module a file was loaded from (see make/0). The first clause deals with loading from another file. On reload, this clause will be discarded by $start_consult/1. The second clause deals with reload from the toplevel. Here we avoid creating a duplicate dynamic (i.e., not related to a source) clause.
- $load_ctx_options(+Options, -CtxOptions) is det[private]
- Select the load options that determine the load semantics to perform a proper reload. Delete the others.
- $check_load_non_module(+File) is det[private]
- Test that a non-module file is not loaded into multiple contexts.
- $load_file(+Path, +Id, -Module, +Options)[private]
- '$load_file'/4 does the actual loading.
state(FirstTerm:boolean, Module:atom, AtEnd:atom, Stop:boolean, Id:atom, Dialect:atom)
- $set_dialect(+Dialect, +State)[private]
- Sets the expected dialect. This is difficult if we are compiling
a .qlf file using qcompile/1 because the file is already open,
while we are looking for the first term to decide wether this is
a module or not. We save the dialect and set it after opening
the file or module.
Note that expects_dialect/1 itself may be autoloaded from the library.
- $reset_dialect(+File, +Class) is det[private]
- Load .pl files from the SWI-Prolog distribution always in
swi
dialect. - $module3(+Spec) is det[private]
- Handle the 3th argument of a module declartion.
- $module_name(?Name, +Id, -Module, +Options) is semidet[private]
- Determine the module name. There are some cases:
- Option
module(Module)
is given. In that case, use this module and if Module is the load context, ignore the module header. - The initial name is unbound. Use the base name of the source identifier (normally the file name). Compatibility to Ciao. This might change; I think it is wiser to use the full unique source identifier.
- Option
- $redefine_module(+Module, +File, -Redefine)[private]
- $module_class(+File, -Class, -Super) is det[private]
- Determine the file class and initial module from which File
inherits. All boot and library modules as well as the -F script
files inherit from
system
, while all normal user modules inherit fromuser
. - $import_list(+TargetModule, +FromModule, +Import, +Reexport) is det[private]
- Import from FromModule to TargetModule. Import is one of
all
, a list of optionally mapped predicate indicators or a termexcept(Import)
. - $import_all(+Import, +Context, +Source, +Reexport, +Strength)[private]
- $import_all2(+Imports, +Context, +Source, -Imported, -ImpOps, +Strength)[private]
- $exported_ops(+Module, -Ops, ?Tail) is det[private]
- Ops is a list of
op(P,A,N)
terms representing the operators exported from Module. - $import_ops(+Target, +Source, +Pattern)[private]
- Import the operators export from Source into the module table of Target. We only import operators that unify with Pattern.
- $export_list(+Declarations, +Module, -Ops)[private]
- Handle the export list of the module declaration for Module associated to File.
- $execute_directive(:Goal, +File) is det[private]
- Execute the argument of :- or ?- while loading a file.
- $valid_directive(:Directive) is det[private]
- If the flag
sandboxed_load
istrue
, this calls prolog:sandbox_allowed_directive/1. This call can deny execution of the directive by throwing an exception. - $store_admin_clause(+Clause, ?Layout, +Owner, +SrcLoc) is det[private]
- Store a clause into the database for administrative purposes. This bypasses sanity checking.
- $store_clause(+Clause, ?Layout, +Owner, +SrcLoc) is det[private]
- Store a clause into the database.
- $store_clause(+Term, +Id) is det[private]
- This interface is used by PlDoc (and who knows). Kept for to avoid compatibility issues.
- compile_aux_clauses(+Clauses) is det[private]
- Compile clauses given the current source location but do not
change the notion of the current procedure such that
discontiguous warnings are not issued. The clauses are
associated with the current file and therefore wiped out if the
file is reloaded.
If the cross-referencer is active, we should not (re-)assert the clauses. Actually, we should make them known to the cross-referencer. How do we do that? Maybe we need a different API, such as in:
expand_term_aux(Goal, NewGoal, Clauses)
- $stage_file(+Target, -Stage) is det[private]
- $install_staged_file(+Catcher, +Staged, +Target, +OnError)[private]
- Create files using staging, where we first write a temporary file and move it to Target if the file was created successfully. This provides an atomic transition, preventing customers from reading an incomplete file.
- length(?List, ?N)[private]
- Is true when N is the length of List.
- $is_options(@Term) is semidet[private]
- True if Term looks like it provides options.
- $option(?Opt, +Options) is semidet[private]
- $option(?Opt, +Options, +Default) is det[private]
- $select_option(?Opt, +Options, -Rest) is semidet[private]
- Select an option from Options.
- $merge_options(+New, +Default, -Merged) is det[private]
- Add/replace options specified in New.
- at_halt(:Goal)[private]
- Register Goal to be called if the system halts.
- cancel_halt(+Reason)[private]
- This predicate may be called from at_halt/1 handlers to cancel halting the program. If causes halt/0 to fail rather than terminating the process.
- $load_additional_boot_files is det[private]
- Called from
compileFileList()
in pl-wic.c. Gets the files from "-c file ..." and loads them into the module user.