documentation.

This commit is contained in:
Vitor Santos Costa 2018-10-15 13:47:36 +01:00
parent 70cb6ed01e
commit b41986ee3c
10 changed files with 81 additions and 65 deletions

View File

@ -95,5 +95,5 @@ endif()
install(FILES ${PL_BOOT_SOURCES}
DESTINATION ${libpl}/pll
DESTINATION ${libpl}/pl
)

View File

@ -15,6 +15,10 @@
* *
*************************************************************************/
/**
* @file checker.yap
*
*/
:- system_module( style_checker, [no_style_check/1,
style_check/1], ['$check_term'/5,
'$sv_warning'/2,
@ -24,7 +28,7 @@
/**
@defgroup YAPStyle Checker
@defgroup YAPStyleChecker Style Checker
@ingroup YAPCompilerSettings
@{
@ -167,6 +171,6 @@ separated by clauses from other procedures.
discontiguous(P) :- '$discontiguous'(P).
/*
/**
@}
*/

View File

@ -101,6 +101,10 @@ files and to set-up the Prolog environment. We discuss
+ @ref YAPCompilerSettings
@}
*/
/**
@defgroup YAPReadFiles The Predicates that Read Source Files
@ingroup YAPConsulting
@ -1678,6 +1682,10 @@ End of conditional compilation.
current_prolog_flag(source, true), !.
'$fetch_comp_status'(compact).
/** consult_depth(-int:_LV_)
*
* Unify _LV_ with the number of files being consulted.
*/
consult_depth(LV) :- '$show_consult_level'(LV).
prolog_library(File) :-

View File

@ -41,7 +41,7 @@
/**
* @ingroup AttributedVariables_Builtins
* @addtogroup AttributedVariables_Builtins
* @{
*
*
@ -141,42 +141,6 @@ freeze_goal(V,G) :-
'$current_module'(M),
internal_freeze(V, redo_freeze(_Done,V,M:G)).
%
%
% Dif is tricky because we need to wake up on the two variables being
% bound together, or on any variable of the term being bound to
% another. Also, the day YAP fully supports infinite rational trees,
% dif should work for them too. Hence, term comparison should not be
% implemented in Prolog.
%
% This is the way dif works. The '$can_unify' predicate does not know
% anything about dif semantics, it just compares two terms for
% equaility and is based on compare. If it succeeds without generating
% a list of variables, the terms are equal and dif fails. If it fails,
% dif succeeds.
%
% If it succeeds but it creates a list of variables, dif creates
% suspension records for all these variables on the '$redo_dif'(V,
% X, Y) goal. V is a flag that says whether dif has completed or not,
% X and Y are the original goals. Whenever one of these variables is
% bound, it calls '$redo_dif' again. '$redo_dif' will then check whether V
% was bound. If it was, dif has succeeded and redo_dif just
% exits. Otherwise, '$redo_dif' will call dif again to see what happened.
%
% Dif needs two extensions from the suspension engine:
%
% First, it needs
% for the engine to be careful when binding two suspended
% variables. Basically, in this case the engine must be sure to wake
% up one of the goals, as they may make dif fail. The way the engine
% does so is by searching the list of suspended variables, and search
% whether they share a common suspended goal. If they do, that
% suspended goal is added to the WokenList.
%
% Second, thanks to dif we may try to suspend on the same variable
% several times. dif calls a special version of freeze that checks
% whether that is in fact the case.
%
/** @pred dif( _X_, _Y_)
@ -185,6 +149,42 @@ suspend if unification may still succeed or fail, and will fail if they
always unify.
Dif is tricky because we need to wake up on the two variables being
bound together, or on any variable of the term being bound to
another. Also, the day YAP fully supports infinite rational trees,
dif should work for them too. Hence, term comparison should not be
implemented in Prolog.
This is the way dif works. The '$can_unify' predicate does not know
anything about dif semantics, it just compares two terms for
equaility and is based on compare. If it succeeds without generating
a list of variables, the terms are equal and dif fails. If it fails,
dif succeeds.
If it succeeds but it creates a list of variables, dif creates
suspension records for all these variables on the '$redo_dif'(V,
X, Y) goal. V is a flag that says whether dif has completed or not,
X and Y are the original goals. Whenever one of these variables is
bound, it calls '$redo_dif' again. '$redo_dif' will then check whether V
was bound. If it was, dif has succeeded and redo_dif just
exits. Otherwise, '$redo_dif' will call dif again to see what happened.
Dif needs two extensions from the suspension engine:
First, it needs
for the engine to be careful when binding two suspended
variables. Basically, in this case the engine must be sure to wake
up one of the goals, as they may make dif fail. The way the engine
does so is by searching the list of suspended variables, and search
whether they share a common suspended goal. If they do, that
suspended goal is added to the WokenList.
Second, thanks to dif we may try to suspend on the same variable
several times. dif calls a special version of freeze that checks
whether that is in fact the case.
*/
prolog:dif(X, Y) :-
'$can_unify'(X, Y, LVars), !,
@ -198,6 +198,7 @@ dif_suspend_on_lvars([H|T], G) :-
internal_freeze(H, G),
dif_suspend_on_lvars(T, G).
%% @pred redo_dif(_Done_, _X_, _Y_)
%
% This predicate is called whenever a variable dif was suspended on is
% bound. Note that dif may have already executed successfully.
@ -263,7 +264,7 @@ redo_ground('$done', _, Goal) :-
%
% support for when/2 built-in
%
/** @pred when(+ _C_,: _G_)
/** @pred when(+ _C_, 0:_G_)
Delay execution of goal _G_ until the conditions _C_ are

View File

@ -6,7 +6,7 @@
/**
@ingroup ModuleBuiltins
@addtogroup ModuleBuiltins
@{
*/

View File

@ -4,11 +4,10 @@
/** @file preddyns.yap */
/**
* @addtogroup Database
* @{
*
* @addtogroup Internal_Database
* @brief main operations on dynamic predicates.
*
*
*/
/** @pred asserta(+ _C_) is iso

View File

@ -446,7 +446,7 @@ hide_predicate(P0) :-
nonvar(P),
P = N/A,
!,
functor(S,N,A).
functor(_S,N,A).
hide_predicate(P0) :-
strip_module(P0, M, P),
'$hide_predicate'(P, M).

View File

@ -362,7 +362,7 @@ available it tries reconsulting the source file.
qload_module(Mod) :-
prolog_flag(verbose_load, OldF, false),
prolog_flag(verbose, OldV, silent),
Verbosity = silent
Verbosity = silent,
StartMsg = loading_module,
EndMsg = module_loaded,
'$current_module'(SourceModule, Mod),

View File

@ -34,20 +34,21 @@
setof/3], []).
/**
@defgroup Sets Collecting Solutions to a Goal
@ingroup builtins
@{
When there are several solutions to a goal, if the user wants to collect all
the solutions he may be led to use the data base, because backtracking will
forget previous solutions.
YAP allows the programmer to choose from several system
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:
*
* @defgroup Sets Collecting Solutions to a Goal
* @ingroup builtins
* @{
*
*
* When there are several solutions to a goal, if the user wants to collect all
* the solutions he may be led to use the data base, because backtracking will
* forget previous solutions.
*
* YAP allows the programmer to choose from several system
* 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]).

View File

@ -7,8 +7,11 @@
*
* @addtogroup TopLevel Top-Level and Boot Predicates
* @ingroup YAPControl
* @{
*/
*
* [TOC]
*
* @{
* \*/
:- '$system_meta_predicates'([
catch(0,?,0),
@ -923,7 +926,7 @@ expand_term(Term,Expanded) :-
%% @}
%% @addto group YAPControl
%% @addtogroup YAPControl
%% @{