documentation
This commit is contained in:
parent
2d55f41ef6
commit
54c6b8c041
@ -57,6 +57,8 @@ ${CMAKE_SOURCE_DIR}/packages/CLPBN/examples
|
||||
${CMAKE_SOURCE_DIR}/packages/CLPBN/horus
|
||||
${CMAKE_SOURCE_DIR}/packages/prosqlite
|
||||
${CMAKE_SOURCE_DIR}/packages/pyswip
|
||||
${CMAKE_SOURCE_DIR}/packages/python/yap_kernel
|
||||
${CMAKE_SOURCE_DIR}/packages/python/swig
|
||||
${CMAKE_SOURCE_DIR}/packages/yap-lbfgs/liblbfgs-1.10
|
||||
${CMAKE_SOURCE_DIR}/library/dialect/swi/os
|
||||
${CMAKE_SOURCE_DIR}/*/bprolog/*
|
||||
|
@ -7,6 +7,20 @@
|
||||
*/
|
||||
|
||||
|
||||
:- module(arg,
|
||||
[
|
||||
genarg/3,
|
||||
arg0/3,
|
||||
genarg0/3,
|
||||
args/3,
|
||||
args0/3,
|
||||
% project/3
|
||||
path_arg/3
|
||||
]).
|
||||
|
||||
|
||||
|
||||
|
||||
/**
|
||||
*
|
||||
|
||||
@ -33,19 +47,6 @@ This file has been included in the YAP library by Vitor Santos Costa, 2008. No e
|
||||
genarg/3.
|
||||
*/
|
||||
|
||||
:- module(arg,
|
||||
[
|
||||
genarg/3,
|
||||
arg0/3,
|
||||
genarg0/3,
|
||||
args/3,
|
||||
args0/3,
|
||||
% project/3
|
||||
path_arg/3
|
||||
]).
|
||||
|
||||
|
||||
|
||||
/**
|
||||
* @pred arg0( +_Index_, +_Term_ , -_Arg_ )
|
||||
*
|
||||
|
@ -3,9 +3,9 @@
|
||||
* @file assoc.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 13:53:34 2015
|
||||
*
|
||||
*
|
||||
* @brief Red-Black Implementation of Association Lists.
|
||||
*
|
||||
*
|
||||
* This file has been included as an YAP library by Vitor Santos Costa, 1999
|
||||
*
|
||||
* Note: the keys should be bound, the associated values need not be.
|
||||
@ -33,9 +33,11 @@
|
||||
del_max_assoc/4
|
||||
]).
|
||||
|
||||
/** @defgroup Association_Lists Association Lists
|
||||
@ingroup library
|
||||
/**
|
||||
|
||||
@defgroup Assoc Association Maps
|
||||
@{
|
||||
@ingroup library
|
||||
|
||||
The following association list manipulation predicates are available
|
||||
once included with the `use_module(library(assoc))` command. The
|
||||
@ -45,9 +47,7 @@ red-black trees library and emulates the SICStus Prolog interface.
|
||||
|
||||
The library exports the following definitions:
|
||||
|
||||
- is/assoc/1
|
||||
|
||||
|
||||
*/
|
||||
|
||||
|
||||
@ -77,27 +77,27 @@ The library exports the following definitions:
|
||||
rb_del_max/4
|
||||
]).
|
||||
|
||||
/** @pred empty_assoc(+ _Assoc_)
|
||||
/** @pred empty_assoc(+ _Assoc_)
|
||||
|
||||
Succeeds if association list _Assoc_ is empty.
|
||||
|
||||
|
||||
*/
|
||||
empty_assoc(t).
|
||||
|
||||
/** @pred assoc_to_list(+ _Assoc_,? _List_)
|
||||
/** @pred assoc_to_list(+ _Assoc_,? _List_)
|
||||
|
||||
|
||||
Given an association list _Assoc_ unify _List_ with a list of
|
||||
the form _Key-Val_, where the elements _Key_ are in ascending
|
||||
order.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
assoc_to_list(t, L) :- !, L = [].
|
||||
assoc_to_list(T, L) :-
|
||||
rb_visit(T, L).
|
||||
|
||||
/** @pred is_assoc(+ _Assoc_)
|
||||
/** @pred is_assoc(+ _Assoc_)
|
||||
|
||||
Succeeds if _Assoc_ is an association list, that is, if it is a
|
||||
red-black tree.
|
||||
@ -106,57 +106,57 @@ is_assoc(t) :- !.
|
||||
is_assoc(T) :-
|
||||
is_rbtree(T).
|
||||
|
||||
/** @pred min_assoc(+ _Assoc_,- _Key_,? _Value_)
|
||||
/** @pred min_assoc(+ _Assoc_,- _Key_,? _Value_)
|
||||
|
||||
|
||||
Given the association list
|
||||
_Assoc_, _Key_ in the smallest key in the list, and _Value_
|
||||
the associated value.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
min_assoc(T,K,V) :-
|
||||
rb_min(T,K,V).
|
||||
|
||||
/** @pred max_assoc(+ _Assoc_,- _Key_,? _Value_)
|
||||
/** @pred max_assoc(+ _Assoc_,- _Key_,? _Value_)
|
||||
|
||||
|
||||
Given the association list
|
||||
_Assoc_, _Key_ in the largest key in the list, and _Value_
|
||||
the associated value.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
max_assoc(T,K,V) :-
|
||||
rb_max(T,K,V).
|
||||
|
||||
/** @pred gen_assoc( ?Key, +Assoc, ?Valu_)
|
||||
/** @pred gen_assoc( ?Key, +Assoc, ?Valu_)
|
||||
|
||||
|
||||
Given the association list _Assoc_, unify _Key_ and _Value_
|
||||
with a key-value pair in the list. It can be used to enumerate all elements
|
||||
in the association list.
|
||||
in the association list.
|
||||
*/
|
||||
gen_assoc(K, T, V) :-
|
||||
rb_in(K,V,T).
|
||||
|
||||
/** @pred get_assoc(+ _Key_,+ _Assoc_,? _Value_)
|
||||
/** @pred get_assoc(+ _Key_,+ _Assoc_,? _Value_)
|
||||
|
||||
|
||||
If _Key_ is one of the elements in the association list _Assoc_,
|
||||
return the associated value.
|
||||
return the associated value.
|
||||
*/
|
||||
get_assoc(K,T,V) :-
|
||||
rb_lookup(K,V,T).
|
||||
|
||||
/** @pred get_assoc(+ _Key_,+ _Assoc_,? _Value_,+ _NAssoc_,? _NValue_)
|
||||
/** @pred get_assoc(+ _Key_,+ _Assoc_,? _Value_,+ _NAssoc_,? _NValue_)
|
||||
|
||||
|
||||
If _Key_ is one of the elements in the association list _Assoc_,
|
||||
return the associated value _Value_ and a new association list
|
||||
_NAssoc_ where _Key_ is associated with _NValue_.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
get_assoc(K,T,V,NT,NV) :-
|
||||
rb_update(T,K,V,NV,NT).
|
||||
@ -166,52 +166,52 @@ get_assoc(K,T,V,NT,NV) :-
|
||||
If _Key_ is one of the elements in the association list _Assoc_,
|
||||
return the next key, _Next_, and its value, _Value_.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
get_next_assoc(K,T,KN,VN) :-
|
||||
rb_next(T,K,KN,VN).
|
||||
|
||||
/** @pred get_prev_assoc(+ _Key_,+ _Assoc_,? _Next_,? _Value_)
|
||||
/** @pred get_prev_assoc(+ _Key_,+ _Assoc_,? _Next_,? _Value_)
|
||||
|
||||
|
||||
If _Key_ is one of the elements in the association list _Assoc_,
|
||||
return the previous key, _Next_, and its value, _Value_.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
get_prev_assoc(K,T,KP,VP) :-
|
||||
rb_previous(T,K,KP,VP).
|
||||
|
||||
/** @pred list_to_assoc(+ _List_,? _Assoc_)
|
||||
/** @pred list_to_assoc(+ _List_,? _Assoc_)
|
||||
|
||||
|
||||
Given a list _List_ such that each element of _List_ is of the
|
||||
form _Key-Val_, and all the _Keys_ are unique, _Assoc_ is
|
||||
the corresponding association list.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
list_to_assoc(L, T) :-
|
||||
list_to_rbtree(L, T).
|
||||
|
||||
/** @pred ord_list_to_assoc(+ _List_,? _Assoc_)
|
||||
/** @pred ord_list_to_assoc(+ _List_,? _Assoc_)
|
||||
|
||||
|
||||
Given an ordered list _List_ such that each element of _List_ is
|
||||
of the form _Key-Val_, and all the _Keys_ are unique, _Assoc_ is
|
||||
the corresponding association list.
|
||||
|
||||
|
||||
*/
|
||||
ord_list_to_assoc(L, T) :-
|
||||
ord_list_to_rbtree(L, T).
|
||||
|
||||
/** @pred map_assoc(+ _Pred_,+ _Assoc_)
|
||||
/** @pred map_assoc(+ _Pred_,+ _Assoc_)
|
||||
|
||||
|
||||
Succeeds if the unary predicate name _Pred_( _Val_) holds for every
|
||||
element in the association list.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
map_assoc(t, _) :- !.
|
||||
map_assoc(P, T) :-
|
||||
@ -239,7 +239,7 @@ extract_mod(M:G, _, FM, FG ) :- !,
|
||||
extract_mod(G, M, FM, FG ).
|
||||
extract_mod(G, M, M, G ).
|
||||
|
||||
/** @pred put_assoc(+ _Key_,+ _Assoc_,+ _Val_,+ _New_)
|
||||
/** @pred put_assoc(+ _Key_,+ _Assoc_,+ _Val_,+ _New_)
|
||||
|
||||
The association list _New_ includes and element of association
|
||||
_key_ with _Val_, and all elements of _Assoc_ that did not
|
||||
@ -253,35 +253,35 @@ put_assoc(K, t, V, NT) :- !,
|
||||
put_assoc(K, T, V, NT) :-
|
||||
rb_insert(T, K, V, NT).
|
||||
|
||||
/** @pred del_assoc(+ _Key_, + _Assoc_, ? _Val_, ? _NewAssoc_)
|
||||
/** @pred del_assoc(+ _Key_, + _Assoc_, ? _Val_, ? _NewAssoc_)
|
||||
|
||||
|
||||
Succeeds if _NewAssoc_ is an association list, obtained by removing
|
||||
the element with _Key_ and _Val_ from the list _Assoc_.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
del_assoc(K, T, V, NT) :-
|
||||
rb_delete(T, K, V, NT).
|
||||
|
||||
/** @pred del_min_assoc(+ _Assoc_, ? _Key_, ? _Val_, ? _NewAssoc_)
|
||||
/** @pred del_min_assoc(+ _Assoc_, ? _Key_, ? _Val_, ? _NewAssoc_)
|
||||
|
||||
|
||||
Succeeds if _NewAssoc_ is an association list, obtained by removing
|
||||
the smallest element of the list, with _Key_ and _Val_
|
||||
from the list _Assoc_.
|
||||
|
||||
|
||||
*/
|
||||
del_min_assoc(T, K, V, NT) :-
|
||||
rb_del_min(T, K, V, NT).
|
||||
|
||||
/** @pred del_max_assoc(+ _Assoc_, ? _Key_, ? _Val_, ? _NewAssoc_)
|
||||
/** @pred del_max_assoc(+ _Assoc_, ? _Key_, ? _Val_, ? _NewAssoc_)
|
||||
|
||||
|
||||
Succeeds if _NewAssoc_ is an association list, obtained by removing
|
||||
the largest element of the list, with _Key_ and _Val_ from the
|
||||
list _Assoc_.
|
||||
|
||||
|
||||
*/
|
||||
del_max_assoc(T, K, V, NT) :-
|
||||
rb_del_max(T, K, V, NT).
|
||||
|
@ -14,7 +14,9 @@
|
||||
* comments: attribute support for Prolog *
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
* @file atts.yap
|
||||
*/
|
||||
:- module(attributes, [op(1150, fx, attribute)]).
|
||||
|
||||
/**
|
||||
|
@ -1,4 +1,7 @@
|
||||
/**
|
||||
* @file autoloader.yap
|
||||
|
||||
*/
|
||||
:- module(autoloader,[make_library_index/0]).
|
||||
|
||||
:- use_module(library(lists),[append/3]).
|
||||
@ -60,7 +63,7 @@ scan_exports(Library, CallName) :-
|
||||
close(W).
|
||||
scan_exports(Library) :-
|
||||
format(user_error,'[ warning: library ~w not defined ]~n',[Library]).
|
||||
|
||||
|
||||
%
|
||||
% SWI is the only language that uses autoload.
|
||||
%
|
||||
@ -74,7 +77,7 @@ scan_swi_exports :-
|
||||
open(Path, read, O),
|
||||
get_exports(O, Exports, Module),
|
||||
get_reexports(O, Reexports, Exports),
|
||||
close(O),
|
||||
close(O),
|
||||
open('dialect/swi/INDEX.pl', write, W),
|
||||
publish_exports(Reexports, W, library(dialect/swi), Module),
|
||||
close(W).
|
||||
@ -115,7 +118,7 @@ find_predicate(G,ExportingModI) :-
|
||||
ensure_file_loaded(File).
|
||||
find_predicate(G,ExportingModI) :-
|
||||
var(G),
|
||||
index(Name,Arity,ExportingModI,File),
|
||||
index(Name,Arity,ExportingModI,File),
|
||||
functor(G, Name, Arity),
|
||||
ensure_file_loaded(File).
|
||||
|
||||
@ -124,4 +127,3 @@ ensure_file_loaded(File) :-
|
||||
ensure_file_loaded(File) :-
|
||||
load_files(autoloader:File,[silent(true),if(not_loaded)]),
|
||||
assert(loaded(File)).
|
||||
|
||||
|
@ -84,6 +84,7 @@
|
||||
@addtogroup YAPControl
|
||||
@ingroup builtins
|
||||
@{
|
||||
|
||||
*/
|
||||
|
||||
/** @pred forall(: _Cond_,: _Action_)
|
||||
@ -124,7 +125,7 @@ Call goal _H_ once per each solution of goal _H_. If goal
|
||||
_H_ has no solutions, call goal _I_.
|
||||
|
||||
The built-in `if/3` is similar to `->/3`, with the difference
|
||||
that it will backtrack over the test goal. Consider the following
|
||||
that it will backtrack over the test https://wiki.python.org/moin/HandlingExceptionsgoal. Consider the following
|
||||
small data-base:
|
||||
|
||||
~~~~~{.prolog}
|
||||
|
@ -3,15 +3,9 @@
|
||||
* @file dialect.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP-2.lan>
|
||||
* @date Thu Oct 19 10:50:33 2017
|
||||
*
|
||||
* @brief support Prolog dialects
|
||||
*
|
||||
* @defgroup Dialects Compatibility with other Prolog dialects
|
||||
* @ingroup extensions
|
||||
* @{
|
||||
* @brief Prolog dialects
|
||||
*
|
||||
*/
|
||||
* @brief support Prolog dialects
|
||||
*/
|
||||
|
||||
|
||||
:- module(dialect,
|
||||
@ -20,18 +14,27 @@
|
||||
source_exports/2
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup Dialects Compatibility with other Prolog dialects
|
||||
* @ingroup extensions
|
||||
* @{
|
||||
* @brief Prolog dialects
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- use_system_module( '$_errors', ['$do_error'/2]).
|
||||
|
||||
|
||||
%
|
||||
|
||||
%%
|
||||
% @pred expects_dialect(+Dialect)
|
||||
%
|
||||
% True if YAP can enable support for a different Prolog dialect.
|
||||
% True if YAP can enable support for a different Prolog dialect.
|
||||
% Currently there is support for bprolog, hprolog and swi-prolog.
|
||||
% Notice that this support may be incomplete.
|
||||
%
|
||||
% The
|
||||
%
|
||||
prolog:expects_dialect(yap) :- !,
|
||||
eraseall('$dialect'),
|
||||
recorda('$dialect',yap,_).
|
||||
|
@ -21,8 +21,10 @@
|
||||
* @date Thu Oct 19 11:47:38 2017
|
||||
*
|
||||
* @brief Control File Loading
|
||||
%
|
||||
% @defgroup Directives Prolog Directives
|
||||
%/
|
||||
|
||||
/**
|
||||
* @defgroup Directives Prolog Directives
|
||||
* @ingroup YAPConsulting
|
||||
* @{
|
||||
*
|
||||
|
@ -27,6 +27,7 @@
|
||||
/**
|
||||
@defgroup SWI-error High-level error testing.
|
||||
@ingroup Deb_Interaction
|
||||
@{
|
||||
|
||||
This SWI module provides predicates to simplify error generation and
|
||||
checking. Adapted to use YAP built-ins.
|
||||
@ -39,8 +40,6 @@ most common ISO error terms.
|
||||
|
||||
YAP reuses the code with some extensions, and supports interfacing to some C-builtins.
|
||||
|
||||
@{
|
||||
|
||||
*/
|
||||
|
||||
:- multifile
|
||||
|
@ -19,6 +19,7 @@
|
||||
/** @defgroup YAPErrorHandler Error Handling
|
||||
|
||||
@ingroup YAPErrors
|
||||
@{
|
||||
|
||||
The error handler is called when there is an execution error or a
|
||||
warning needs to be displayed. The handlers include a number of hooks
|
||||
@ -38,8 +39,6 @@ Errors are terms of the form:
|
||||
- error( type_error( Type, Culprit )`
|
||||
- error( uninstantiation_error( Culprit )`
|
||||
|
||||
@{
|
||||
|
||||
*/
|
||||
|
||||
:- system_module( '$_errors', [system_error/2], ['$Error'/1,
|
||||
|
24
pl/eval.yap
24
pl/eval.yap
@ -19,19 +19,21 @@
|
||||
* @file eval.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP-2.lan>
|
||||
* @date Thu Oct 19 11:52:48 2017
|
||||
*
|
||||
* @brief compiling expressions
|
||||
*
|
||||
* @defgroup CompiledExpression A Compiler for Arithmetic
|
||||
* @brief compiling expressions
|
||||
*/
|
||||
:- system_module( '$_eval', [], ['$full_clause_optimisation'/4]).
|
||||
|
||||
:- use_system_module( terms, [new_variables_in_term/3,
|
||||
variables_within_term/3]).
|
||||
|
||||
/**
|
||||
*
|
||||
* @defgroup CompiledExpression A Compiler for Arithmetic
|
||||
* @ingroup drectives
|
||||
*
|
||||
*
|
||||
*
|
||||
* @{
|
||||
*/
|
||||
:- system_module( '$_eval', [], ['$full_clause_optimisation'/4]).
|
||||
|
||||
:- use_system_module( terms, [new_variables_in_term/3,
|
||||
variables_within_term/3]).
|
||||
|
||||
:- multifile '$full_clause_optimisation'/4.
|
||||
|
||||
|
||||
@ -138,3 +140,5 @@
|
||||
%, portray_clause((H:-BF))
|
||||
'$full_clause_optimisation'(H, M, B0, BF) :-
|
||||
'$localise_vars_opt'(H, M, B0, BF), !.
|
||||
|
||||
%% @}
|
||||
|
@ -17,10 +17,13 @@
|
||||
/**
|
||||
* @file pl/flags.yap
|
||||
*
|
||||
/
|
||||
|
||||
/**
|
||||
* @defgroup YAPFlags Yap Flags
|
||||
*
|
||||
* @{
|
||||
* @ingroup builtins
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
|
@ -25,6 +25,20 @@
|
||||
*
|
||||
*/
|
||||
|
||||
:- system_module( '$_grammar', [!/2,
|
||||
(',')/4,
|
||||
(->)/4,
|
||||
('.')/4,
|
||||
(;)/4,
|
||||
'C'/3,
|
||||
[]/2,
|
||||
[]/4,
|
||||
(\+)/3,
|
||||
phrase/2,
|
||||
phrase/3,
|
||||
{}/3,
|
||||
('|')/4], ['$do_error'/2]).
|
||||
|
||||
/**
|
||||
@defgroup Grammars Grammar Rules
|
||||
@ingroup builtins
|
||||
@ -67,20 +81,6 @@ right hand side of a grammar rule
|
||||
Grammar related built-in predicates:
|
||||
|
||||
*/
|
||||
:- system_module( '$_grammar', [!/2,
|
||||
(',')/4,
|
||||
(->)/4,
|
||||
('.')/4,
|
||||
(;)/4,
|
||||
'C'/3,
|
||||
[]/2,
|
||||
[]/4,
|
||||
(\+)/3,
|
||||
phrase/2,
|
||||
phrase/3,
|
||||
{}/3,
|
||||
('|')/4], ['$do_error'/2]).
|
||||
|
||||
|
||||
% :- meta_predicate ^(?,0,?).
|
||||
% ^(Xs, Goal, Xs) :- call(Goal).
|
||||
|
@ -19,12 +19,16 @@
|
||||
* @file ground.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP-2.lan>
|
||||
* @date Thu Oct 19 12:01:27 2017
|
||||
*
|
||||
*
|
||||
* @brief term operations
|
||||
*
|
||||
*/
|
||||
|
||||
/**
|
||||
* @addtogroup YAPTypes
|
||||
*
|
||||
*
|
||||
* @{
|
||||
*
|
||||
*
|
||||
*/
|
||||
/*
|
||||
% grounds all free variables
|
||||
@ -63,7 +67,7 @@ numbervars(Term, M, N) :-
|
||||
'$numbermarked_vars'(L, M, N).
|
||||
|
||||
'$numbermarked_vars'([], M, M).
|
||||
'$numbermarked_vars'([V|L], M, N) :-
|
||||
'$numbermarked_vars'([V|L], M, N) :-
|
||||
attvar(V), !,
|
||||
'$numbermarked_vars'(L, M, N).
|
||||
'$numbermarked_vars'(['$VAR'(M)|L], M, N) :-
|
||||
@ -72,3 +76,4 @@ numbervars(Term, M, N) :-
|
||||
|
||||
*/
|
||||
|
||||
%% @}
|
||||
|
@ -41,7 +41,7 @@
|
||||
**/
|
||||
|
||||
|
||||
/** hacks:context_variables(-NamedVariables)
|
||||
/** yap_hacks:context_variables(-NamedVariables)
|
||||
Access variable names.
|
||||
|
||||
Unify NamedVariables with a list of terms _Name_=_V_
|
||||
|
@ -1,3 +1,15 @@
|
||||
/**
|
||||
** @file imports.yapi
|
||||
*
|
||||
* @brief Module systemm code to import predicates
|
||||
*
|
||||
* This code does not provide visible builtins.
|
||||
*/
|
||||
|
||||
/**
|
||||
* @ingroup ModuleBuiltins
|
||||
* @{
|
||||
*/
|
||||
:- '$mk_dynamic'('$parent_module'(_,_),prolog).
|
||||
|
||||
|
||||
@ -41,4 +53,9 @@
|
||||
'$undefined'(G, ImportingMod)
|
||||
),
|
||||
'$get_undefined_predicates'(G, ImportingMod, G0, ExportingMod),
|
||||
ExportingMod \= ImportingMod.
|
||||
ExportingMod \= ImportingMod.
|
||||
|
||||
/**
|
||||
*
|
||||
* @}
|
||||
*/
|
||||
|
@ -22,7 +22,8 @@
|
||||
*/
|
||||
|
||||
/**
|
||||
* @insection YAPControl
|
||||
* @ingroup YAPControl
|
||||
* @{
|
||||
*
|
||||
*/
|
||||
|
||||
@ -210,3 +211,7 @@
|
||||
'$extend_file_search_path'(P).
|
||||
'$init_path_extensions'.
|
||||
|
||||
/**
|
||||
*
|
||||
* @}
|
||||
*/
|
||||
|
@ -15,7 +15,11 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
|
||||
/**
|
||||
* @file load_foreign.yap
|
||||
*
|
||||
* @brief load predicates written in C (also C++, Java, Python, R)
|
||||
*/
|
||||
:- system_module( '$_load_foreign', [load_foreign_files/3,
|
||||
open_shared_object/2,
|
||||
open_shared_object/3], ['$import_foreign'/3]).
|
||||
|
@ -26,9 +26,17 @@
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(system('$messages'),
|
||||
[system_message/4,
|
||||
prefix/6,
|
||||
prefix/5,
|
||||
file_location/3]).
|
||||
|
||||
/**
|
||||
|
||||
@defgroup Messages Message Handling
|
||||
@{
|
||||
@ingroup YAPControl
|
||||
|
||||
The interaction between YAP and the user relies on YAP's ability to
|
||||
@ -92,19 +100,10 @@ In YAP, the info field describes:
|
||||
- user_message () - ttext on the event.
|
||||
|
||||
|
||||
|
||||
@{
|
||||
|
||||
*/
|
||||
|
||||
|
||||
|
||||
:- module(system('$messages'),
|
||||
[system_message/4,
|
||||
prefix/6,
|
||||
prefix/5,
|
||||
file_location/3]).
|
||||
|
||||
:- abolish(prolog:print_message/2).
|
||||
|
||||
:- use_system_module( user, [message_hook/3]).
|
||||
|
@ -1,10 +1,14 @@
|
||||
/**
|
||||
|
||||
@file meta.yap
|
||||
*/
|
||||
|
||||
/**
|
||||
@defgroup YAPMetaPredicates Using Meta-Calls with Modules
|
||||
|
||||
@{
|
||||
|
||||
@{
|
||||
|
||||
@defgroup YAPMetaPredicates Using Meta-Calls with Modules
|
||||
@ingroup YAPModules
|
||||
|
||||
*/
|
||||
|
@ -5,7 +5,9 @@
|
||||
* @date Sat Apr 7 03:08:03 2018
|
||||
*
|
||||
* @brief meta=declarations, must be run early.
|
||||
*
|
||||
*/
|
||||
|
||||
/**
|
||||
* @addtogroup Meta-Calls The Module System versus the meta-call.
|
||||
* @ingroup YAPMetaPredicates
|
||||
* @{
|
||||
|
@ -18,13 +18,7 @@
|
||||
|
||||
/**
|
||||
@file modules.yap
|
||||
|
||||
@defgroup ModuleBuiltins Module Support
|
||||
|
||||
@ingroup YAPModules
|
||||
@{
|
||||
|
||||
**/
|
||||
*/
|
||||
:- system_module( '$_modules', [abolish_module/1,
|
||||
add_import_module/3,
|
||||
current_module/1,
|
||||
@ -58,6 +52,13 @@
|
||||
'$module_transparent'/2,
|
||||
'$module_transparent'/4]).
|
||||
|
||||
/**
|
||||
@defgroup ModuleBuiltins Module Support
|
||||
|
||||
@ingroup YAPModules
|
||||
@{
|
||||
|
||||
**/
|
||||
|
||||
|
||||
:- use_system_module( '$_arith', ['$c_built_in'/3]).
|
||||
|
@ -2,9 +2,12 @@
|
||||
|
||||
@file newmod.yap
|
||||
@brief support for creating a new module.
|
||||
*/
|
||||
|
||||
/**
|
||||
|
||||
@ingroup ModuleBuiltins
|
||||
|
||||
@{
|
||||
*/
|
||||
|
||||
|
||||
@ -253,3 +256,5 @@ set_module_property(Mod, class(Class)) :-
|
||||
).
|
||||
'$clean_conversion'([P|_], _List, _, _, _, Goal) :-
|
||||
'$do_error'(domain_error(module_export_predicates,P), Goal).
|
||||
|
||||
%% @}
|
||||
|
@ -8,7 +8,9 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
|
||||
/**
|
||||
* @file os.yap
|
||||
*/
|
||||
:- system_module( '$os', [
|
||||
cd/0,
|
||||
cd/1,
|
||||
@ -24,13 +26,13 @@
|
||||
|
||||
/**
|
||||
@defgroup YAPOS Access to Operating System Functionality
|
||||
|
||||
%% @{
|
||||
@ingroup builtins
|
||||
|
||||
The following built-in predicates allow access to underlying
|
||||
Operating System functionality.
|
||||
|
||||
%% @{
|
||||
|
||||
*/
|
||||
|
||||
/** @pred cd
|
||||
|
@ -1,10 +1,15 @@
|
||||
/**
|
||||
* @file pathconf.yap
|
||||
*
|
||||
*/
|
||||
|
||||
/**
|
||||
@defgroup pathconf Configuration of the Prolog file search path
|
||||
|
||||
@{
|
||||
@ingroup AbsoluteFileName
|
||||
|
||||
Prolog systems search follow a complex search on order to track down files.
|
||||
|
||||
@{
|
||||
**/
|
||||
:- module(user).
|
||||
|
||||
|
@ -36,6 +36,7 @@
|
||||
|
||||
/**
|
||||
@defgroup YAPPredDecls Declaring Properties of Predicates
|
||||
@{
|
||||
@ingroup YAPCompilerSettings
|
||||
|
||||
The YAP Compiler allows the programmer to include declarations with
|
||||
@ -273,3 +274,6 @@ its caller.
|
||||
'$predicate_flags'(P, M, Fl, Fl),
|
||||
NFlags is Fl \/ 0x200004,
|
||||
'$predicate_flags'(P, M, Fl, NFlags).
|
||||
/**
|
||||
* @}
|
||||
*/
|
||||
|
@ -4,10 +4,10 @@
|
||||
/** @file preddyns.yap */
|
||||
|
||||
/**
|
||||
* @{
|
||||
* @addtogroup Database
|
||||
|
||||
Next follow the main operations on dynamic predicates.
|
||||
* @{
|
||||
*
|
||||
* @brief main operations on dynamic predicates.
|
||||
|
||||
*/
|
||||
|
||||
@ -348,4 +348,4 @@ dynamic_predicate(P,Sem) :-
|
||||
Sem \= immediate, Sem \= logical, !,
|
||||
'$do_error'(domain_error(semantics_indicator,Sem),Goal).
|
||||
|
||||
%% @}
|
||||
%% @}
|
||||
|
47
pl/preds.yap
47
pl/preds.yap
@ -16,26 +16,8 @@
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
* @{
|
||||
* @defgroup Database The Clausal Data Base
|
||||
* @ingroup builtins
|
||||
|
||||
Predicates in YAP may be dynamic or static. By default, when
|
||||
consulting or reconsulting, predicates are assumed to be static:
|
||||
execution is faster and the code will probably use less space.
|
||||
Static predicates impose some restrictions: in general there can be no
|
||||
addition or removal of clauses for a procedure if it is being used in the
|
||||
current execution.
|
||||
|
||||
Dynamic predicates allow programmers to change the Clausal Data Base with
|
||||
the same flexibility as in C-Prolog. With dynamic predicates it is
|
||||
always possible to add or remove clauses during execution and the
|
||||
semantics will be the same as for C-Prolog. But the programmer should be
|
||||
aware of the fact that asserting or retracting are still expensive operations,
|
||||
and therefore he should try to avoid them whenever possible.
|
||||
|
||||
*/
|
||||
|
||||
* @file preds.yap
|
||||
*/
|
||||
:- system_module( '$_preds', [abolish/1,
|
||||
abolish/2,
|
||||
assert/1,
|
||||
@ -76,6 +58,27 @@ and therefore he should try to avoid them whenever possible.
|
||||
'$unknown_error'/1,
|
||||
'$unknown_warning'/1]).
|
||||
|
||||
/**
|
||||
* @defgroup Database The Clausal Data Base
|
||||
* @{
|
||||
* @ingroup builtins
|
||||
|
||||
Predicates in YAP may be dynamic or static. By default, when
|
||||
consulting or reconsulting, predicates are assumed to be static:
|
||||
execution is faster and the code will probably use less space.
|
||||
Static predicates impose some restrictions: in general there can be no
|
||||
addition or removal of clauses for a procedure if it is being used in the
|
||||
current execution.
|
||||
|
||||
Dynamic predicates allow programmers to change the Clausal Data Base with
|
||||
the same flexibility as in C-Prolog. With dynamic predicates it is
|
||||
always possible to add or remove clauses during execution and the
|
||||
semantics will be the same as for C-Prolog. But the programmer should be
|
||||
aware of the fact that asserting or retracting are still expensive operations,
|
||||
and therefore he should try to avoid them whenever possible.
|
||||
|
||||
*/
|
||||
|
||||
:- use_system_module( '$_boot', ['$check_head_and_body'/4,
|
||||
'$check_if_reconsulted'/2,
|
||||
'$head_and_body'/3,
|
||||
@ -218,7 +221,7 @@ clause(V0,Q,R) :-
|
||||
'$init_preds' :-
|
||||
once('$do_log_upd_clause_erase'(_,_,_,_,_,_)),
|
||||
fail.
|
||||
|
||||
|
||||
'$init_preds'.
|
||||
|
||||
:- '$init_preds'.
|
||||
@ -417,7 +420,7 @@ abolish(X0) :-
|
||||
'$purge_clauses'(G, M), fail.
|
||||
'$abolishs'(_, _).
|
||||
|
||||
/** @pred stash_predicate(+ _Pred_)
|
||||
/** @pred stash_predicate(+ _Pred_)
|
||||
Make predicate _Pred_ invisible to new code, and to `current_predicate/2`,
|
||||
`listing`, and friends. New predicates with the same name and
|
||||
functor can be declared.
|
||||
|
@ -22,9 +22,9 @@
|
||||
showprofres/0,
|
||||
showprofres/1], []).
|
||||
|
||||
/** @defgroup The_Count_Profiler The Count Profiler
|
||||
@ingroup Profiling
|
||||
@{
|
||||
/**
|
||||
* @ingroup Profiling
|
||||
* @{
|
||||
|
||||
The count profiler works by incrementing counters at procedure entry or
|
||||
backtracking. It provides exact information:
|
||||
@ -65,7 +65,7 @@ write_profile_data([D-[M:P|R]|SLP]) :-
|
||||
These are the current predicates to access and clear profiling data:
|
||||
|
||||
|
||||
|
||||
|
||||
*/
|
||||
|
||||
|
||||
@ -77,7 +77,7 @@ These are the current predicates to access and clear profiling data:
|
||||
% describing a predicate; used e.g. on the tick profiler defined below
|
||||
:- multifile(user:prolog_predicate_name/2).
|
||||
|
||||
/** @pred profile_data( ?Na/Ar, ?Parameter, -Data_)
|
||||
/** @pred profile_data( ?Na/Ar, ?Parameter, -Data_)
|
||||
|
||||
|
||||
Give current profile data on _Parameter_ for a predicate described
|
||||
@ -92,7 +92,7 @@ Number of times a procedure was called.
|
||||
Number of times a call to the procedure was backtracked to and retried.
|
||||
|
||||
|
||||
+ profile_reset
|
||||
+ profile_reset
|
||||
|
||||
|
||||
Reset all profiling information.
|
||||
@ -143,12 +143,12 @@ profile_reset :-
|
||||
fail.
|
||||
profile_reset.
|
||||
|
||||
/** @pred showprofres
|
||||
/** @pred showprofres
|
||||
|
||||
|
||||
Show profiling info.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
showprofres :-
|
||||
showprofres(-1).
|
||||
|
@ -14,11 +14,15 @@
|
||||
* comments: protecting the system functions *
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
:- system_module( '$_protect', [], ['$protect'/0]).
|
||||
/**
|
||||
* @file protect.yap
|
||||
* @addtogroup ProtectCore Freeze System Configuration
|
||||
*/
|
||||
|
||||
:- system_module( '$_protect', [], ['$protect'/0]).
|
||||
|
||||
/**
|
||||
* * @addtogroup ProtectCore Freeze System Configuration
|
||||
* @{
|
||||
* @ingroup YAPControl
|
||||
*
|
||||
* This protects current code from further changes
|
||||
@ -30,12 +34,12 @@
|
||||
* - fix system predicates
|
||||
* - hide atoms with `$`
|
||||
*/
|
||||
|
||||
|
||||
|
||||
'$protect' :-
|
||||
'$all_current_modules'(M),
|
||||
( sub_atom(M,0,1,_, '$') ; M= prolog; M= system ),
|
||||
new_system_module( M ),
|
||||
new_system_module( M ),
|
||||
fail.
|
||||
'$protect' :-
|
||||
'$current_predicate'(Name,M,P,_),
|
||||
@ -77,3 +81,5 @@
|
||||
'$visible'('$qq_open').
|
||||
'$visible'('$live').
|
||||
'$visible'('$init_prolog').
|
||||
|
||||
%% @}
|
||||
|
15
pl/save.yap
15
pl/save.yap
@ -19,11 +19,14 @@
|
||||
* @file save.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP-2.lan>
|
||||
* @date Thu Oct 19 12:10:47 2017
|
||||
*
|
||||
* @brief Old Style save
|
||||
*
|
||||
* @brief Old Style save
|
||||
*/
|
||||
|
||||
/**
|
||||
* @addtogroup QLY
|
||||
*
|
||||
* @{
|
||||
*
|
||||
*/
|
||||
|
||||
:- system_module( '$_save', [], []).
|
||||
@ -39,7 +42,7 @@ save(S,OUT) :- '$save'(S,OUT).
|
||||
|
||||
save_program(A) :- var(A), !,
|
||||
'$do_error'(instantiation_error,save_program(A)).
|
||||
save_program(A) :- atom(A), !,
|
||||
save_program(A) :- atom(A), !,
|
||||
atom_codes(A,S),
|
||||
'$save_program2'(S, true).
|
||||
save_program(S) :- '$save_program2'(S, true).
|
||||
@ -95,3 +98,7 @@ restore(A) :- atom(A), !, name(A,S), '$restore'(S).
|
||||
restore(S) :- '$restore'(S).
|
||||
|
||||
*/
|
||||
|
||||
/**
|
||||
* @}
|
||||
*/
|
||||
|
13
pl/setof.yap
13
pl/setof.yap
@ -19,10 +19,10 @@
|
||||
* @file setof.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Thu Nov 19 10:45:32 2015
|
||||
*
|
||||
*
|
||||
* @brief Setof and friends.
|
||||
*
|
||||
*
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
@ -36,6 +36,7 @@
|
||||
/**
|
||||
|
||||
@defgroup Sets Collecting Solutions to a Goal
|
||||
@{
|
||||
@ingroup builtins
|
||||
|
||||
When there are several solutions to a goal, if the user wants to collect all
|
||||
@ -47,10 +48,6 @@ predicates instead of writing his own routines. findall/3 gives you
|
||||
the fastest, but crudest solution. The other built-in predicates
|
||||
post-process the result of the query in several different ways:
|
||||
|
||||
@{
|
||||
|
||||
|
||||
|
||||
*/
|
||||
|
||||
:- use_system_module( '$_boot', ['$catch'/3]).
|
||||
@ -182,7 +179,7 @@ no
|
||||
|
||||
*/
|
||||
setof(Template, Generator, Set) :-
|
||||
|
||||
|
||||
( '$is_list_or_partial_list'(Set) ->
|
||||
true
|
||||
;
|
||||
|
Reference in New Issue
Block a user