Add documentation
This commit is contained in:
@@ -1,15 +1,43 @@
|
||||
/** @defgroup Apply Apply Macros
|
||||
@ingroup library
|
||||
/**
|
||||
* @file apply.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Mon Nov 16 23:00:08 2015
|
||||
*
|
||||
* @brief Stub for maplist and friends
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(apply_stub,[]).
|
||||
|
||||
/**
|
||||
* @file apply.yap
|
||||
* @defgroup apply_stub Apply Predicates
|
||||
|
||||
* @ingroup library
|
||||
|
||||
@{
|
||||
|
||||
This library provides a SWI-compatible set of utilities for applying a
|
||||
predicate to all elements of a list. In practice, the library just forwards
|
||||
definitions from the @ref maplist library library.
|
||||
predicate to all elements of a list.
|
||||
|
||||
The apply library is a _stub_, it just forwards definitions to the
|
||||
@ref maplist library. The predicates forwarded are:
|
||||
|
||||
- maplist/2,
|
||||
- maplist/3,
|
||||
- maplist/4,
|
||||
- maplist/5,
|
||||
- include/3,
|
||||
- exclude/3,
|
||||
- partition/4,
|
||||
- partition/5
|
||||
|
||||
@}
|
||||
|
||||
*/
|
||||
|
||||
:- module(apply,[]).
|
||||
|
||||
:- reexport(library(maplist),
|
||||
[maplist/2,
|
||||
maplist/3,
|
||||
@@ -22,6 +50,3 @@ definitions from the @ref maplist library library.
|
||||
]).
|
||||
|
||||
|
||||
/**
|
||||
@}
|
||||
*/
|
||||
|
@@ -1,4 +1,4 @@
|
||||
% File : apply_macros.yap
|
||||
/% File : apply_macros.yap
|
||||
% Author : E. Alphonse from code by Joachim Schimpf
|
||||
% Updated: 15 June 2002
|
||||
% Purpose: Macros to apply a predicate to all elements
|
||||
@@ -6,6 +6,29 @@
|
||||
|
||||
:- module(apply_macros, []).
|
||||
|
||||
/** @defgroup apply_macros Apply Interface to maplist
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
This library provides a SWI-compatible set of utilities for applying a
|
||||
predicate to all elements of a list.
|
||||
|
||||
The apply library just forwards
|
||||
definitions to the @ref maplist library, these include:
|
||||
|
||||
- maplist/2,
|
||||
- maplist/3,
|
||||
- maplist/4,
|
||||
- maplist/5,
|
||||
- include/3,
|
||||
- exclude/3,
|
||||
- partition/4,
|
||||
- partition/5
|
||||
|
||||
@}
|
||||
|
||||
*/
|
||||
|
||||
:- reexport(maplist).
|
||||
|
||||
:- reexport(mapargs).
|
||||
|
118
library/arg.yap
118
library/arg.yap
@@ -1,6 +1,12 @@
|
||||
% This file has been included as an YAP library by Vitor Santos Costa, 2008
|
||||
/**
|
||||
* @file arg.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 01:08:55 2015
|
||||
*
|
||||
* @brief arg/3 and friends
|
||||
*/
|
||||
|
||||
|
||||
% it is based on the Quintus Prolog arg library
|
||||
|
||||
:- module(arg,
|
||||
[
|
||||
@@ -14,34 +20,140 @@
|
||||
]).
|
||||
|
||||
|
||||
/**
|
||||
* @defgroup arg Term Argument Manipulation.
|
||||
|
||||
@ingroup @library
|
||||
|
||||
Extends arg/3 by including backtracking through arguments and access
|
||||
to sub-arguments,
|
||||
|
||||
- arg0/3
|
||||
- args/3
|
||||
- args0/3
|
||||
- genarg/3
|
||||
- genarg0/3
|
||||
- path_arg/3
|
||||
|
||||
|
||||
It is based on the Quintus Prolog arg library. Except for project, all
|
||||
predicates use the arg/3 argument pattern.
|
||||
|
||||
This file has been included in the YAP library by Vitor Santos Costa, 2008. No error checking is actuallly performed within the package: this left to the C-code thaat implements arg/3 and
|
||||
genarg/3.
|
||||
*/
|
||||
|
||||
/**
|
||||
* @pred arg0( +_Index_, +_Term_ , -_Arg_ )
|
||||
*
|
||||
* Similar to arg/3, but `arg0(0,_T_,_F_)` unifies _F_ with _T_'s principal functor:
|
||||
|
||||
~~~~~~~~~
|
||||
?- arg0(0, f(a,b), A).
|
||||
A = f.
|
||||
?- arg0(1, f(a,b), A).
|
||||
A = a.
|
||||
?- arg0(2, f(a,b), A).
|
||||
A = b.
|
||||
~~~~~~~~~
|
||||
|
||||
*/
|
||||
arg0(0,T,A) :- !,
|
||||
functor(T,A,_).
|
||||
arg0(I,T,A) :-
|
||||
arg(I,T,A).
|
||||
|
||||
/**
|
||||
* @pred genarg0( +_Index_, +_Term_ , -_Arg_ )
|
||||
*
|
||||
* Similar to genarg/3, but `genarg0(0,_T_,_F_)` unifies _F_ with _T_'s principal functor:
|
||||
~~~~~~~~~
|
||||
?- genarg0(I,f(a,b),A).
|
||||
A = f,
|
||||
I = 0 ? ;
|
||||
A = a,
|
||||
I = 1 ? ;
|
||||
A = b,
|
||||
I = 2.
|
||||
~~~~~~~~~
|
||||
|
||||
*/
|
||||
genarg0(I,T,A) :-
|
||||
nonvar(I), !,
|
||||
arg0(I,T,A).
|
||||
genarg0(0,T,A) :-
|
||||
functor(T,A,_).
|
||||
genarg0(I,T,A) :-
|
||||
arg(I,T,A).
|
||||
genarg(I,T,A).
|
||||
|
||||
/**
|
||||
* @pred args( +_Index_, +_ListOfTerms_ , -_ListOfArgs_ )
|
||||
*
|
||||
* Succeeds if _ListOfArgs_ unifies with the application of genarg/3 to every element of _ListOfTerms_.
|
||||
|
||||
It corresponds to calling maplist/3 on genarg/3:
|
||||
~~~~~~~~~
|
||||
args( I, Ts, As) :-
|
||||
maplist( genarg(I), Ts, As).
|
||||
~~~~~~~~~
|
||||
|
||||
Notice that unification allows _ListOfArgs_ to be bound, eg:
|
||||
|
||||
~~~~~~~~~
|
||||
?- args(1, [X1+Y1,X2-Y2,X3*Y3,X4/Y4], [1,1,1,1]).
|
||||
X1 = X2 = X3 = X4 = 1.
|
||||
~~~~~~~~~
|
||||
|
||||
|
||||
*/
|
||||
args(_,[],[]).
|
||||
args(I,[T|List],[A|ArgList]) :-
|
||||
genarg(I, T, A),
|
||||
args(I, List, ArgList).
|
||||
|
||||
/**
|
||||
* @pred args0( +_Index_, +_ListOfTerms_ , -_ListOfArgs_ )
|
||||
*
|
||||
* Succeeds if _ListOfArgs_ unifies with the application of genarg0/3 to every element of _ListOfTerms_.
|
||||
|
||||
It corresponds to calling maplist/3 on genarg0/3:
|
||||
~~~~~~~~~
|
||||
args( I, Ts, As) :-
|
||||
maplist( genarg0(I), Ts, As).
|
||||
~~~~~~~~~
|
||||
|
||||
Notice that unification allows _ListOfArgs_ to be bound, eg:
|
||||
|
||||
~~~~~~~~~
|
||||
?- args(1, [X1+Y1,X2-Y2,X3*Y3,X4/Y4], [1,1,1,1]).
|
||||
X1 = X2 = X3 = X4 = 1.
|
||||
~~~~~~~~~
|
||||
|
||||
|
||||
*/
|
||||
args0(_,[],[]).
|
||||
args0(I,[T|List],[A|ArgList]) :-
|
||||
genarg(I, T, A),
|
||||
args0(I, List, ArgList).
|
||||
|
||||
/**
|
||||
* @pred args0( +_ListOfTerms_ , +_Index_, -_ListOfArgs_ )
|
||||
*
|
||||
* Succeeds if _ListOfArgs_ unifies with the application of genarg0/3 to every element of _ListOfTerms_.
|
||||
|
||||
It corresponds to calling args0/3 but with a different order.
|
||||
*/
|
||||
project(Terms, Index, Args) :-
|
||||
args0(Index, Terms, Args).
|
||||
|
||||
% no error checking here!
|
||||
/**
|
||||
* @pred path_arg( +_Path_ , +_Term_, -_Arg_ )
|
||||
*
|
||||
* Succeeds if _Path_ is empty and _Arg unifies with _Term_, or if _Path_ is a list with _Head_ and _Tail_, genarg/3 succeeds on the current term, and path_arg/3 succeeds on its argument.
|
||||
*
|
||||
* Notice that it can be used to enumerate all possible paths in a term.
|
||||
*/
|
||||
path_arg([], Term, Term).
|
||||
path_arg([Index|Indices], Term, SubTerm) :-
|
||||
genarg(Index, Term, Arg),
|
||||
|
@@ -1,176 +1,17 @@
|
||||
% This file has been included as an YAP library by Vitor Santos Costa, 1999
|
||||
|
||||
% Red-Black Implementation of Association Lists.
|
||||
|
||||
% Note : the keys should be bound, the associated values need not be.
|
||||
|
||||
/** @defgroup Association_Lists Association Lists
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
The following association list manipulation predicates are available
|
||||
once included with the `use_module(library(assoc))` command. The
|
||||
original library used Richard O'Keefe's implementation, on top of
|
||||
unbalanced binary trees. The current code utilises code from the
|
||||
red-black trees library and emulates the SICStus Prolog interface.
|
||||
|
||||
|
||||
/**
|
||||
* @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.
|
||||
*/
|
||||
|
||||
|
||||
/** @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.
|
||||
|
||||
|
||||
*/
|
||||
/** @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_.
|
||||
|
||||
|
||||
*/
|
||||
/** @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_.
|
||||
|
||||
|
||||
*/
|
||||
/** @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_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred empty_assoc(+ _Assoc_)
|
||||
|
||||
|
||||
Succeeds if association list _Assoc_ is empty.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred gen_assoc(+ _Assoc_,? _Key_,? _Value_)
|
||||
|
||||
|
||||
Given the association list _Assoc_, unify _Key_ and _Value_
|
||||
with two associated elements. It can be used to enumerate all elements
|
||||
in the association list.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred get_assoc(+ _Key_,+ _Assoc_,? _Value_)
|
||||
|
||||
|
||||
If _Key_ is one of the elements in the association list _Assoc_,
|
||||
return the associated value.
|
||||
|
||||
|
||||
*/
|
||||
/** @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_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred get_next_assoc(+ _Key_,+ _Assoc_,? _Next_,? _Value_)
|
||||
|
||||
If _Key_ is one of the elements in the association list _Assoc_,
|
||||
return the next key, _Next_, and its value, _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_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred is_assoc(+ _Assoc_)
|
||||
|
||||
|
||||
Succeeds if _Assoc_ is an association list, that is, if it is a
|
||||
red-black tree.
|
||||
|
||||
|
||||
*/
|
||||
/** @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.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred map_assoc(+ _Pred_,+ _Assoc_)
|
||||
|
||||
|
||||
Succeeds if the unary predicate name _Pred_( _Val_) holds for every
|
||||
element in the association list.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred map_assoc(+ _Pred_,+ _Assoc_,? _New_)
|
||||
|
||||
Given the binary predicate name _Pred_ and the association list
|
||||
_Assoc_, _New_ in an association list with keys in _Assoc_,
|
||||
and such that if _Key-Val_ is in _Assoc_, and _Key-Ans_ is in
|
||||
_New_, then _Pred_( _Val_, _Ans_) holds.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred max_assoc(+ _Assoc_,- _Key_,? _Value_)
|
||||
|
||||
|
||||
Given the association list
|
||||
_Assoc_, _Key_ in the largest key in the list, and _Value_
|
||||
the associated 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.
|
||||
|
||||
|
||||
*/
|
||||
/** @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.
|
||||
|
||||
|
||||
*/
|
||||
/** @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
|
||||
have key _Key_.
|
||||
|
||||
|
||||
|
||||
|
||||
*/
|
||||
:- module(assoc, [
|
||||
@@ -193,7 +34,26 @@ have key _Key_.
|
||||
assoc_to_keys/2,
|
||||
del_min_assoc/4,
|
||||
del_max_assoc/4
|
||||
]).
|
||||
]).
|
||||
|
||||
/** @defgroup Association_Lists Association Lists
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
The following association list manipulation predicates are available
|
||||
once included with the `use_module(library(assoc))` command. The
|
||||
original library used Richard O'Keefe's implementation, on top of
|
||||
unbalanced binary trees. The current code utilises code from the
|
||||
red-black trees library and emulates the SICStus Prolog interface.
|
||||
|
||||
The library exports the following definitions:
|
||||
|
||||
- is/assoc/1
|
||||
|
||||
|
||||
*/
|
||||
|
||||
|
||||
|
||||
:- meta_predicate map_assoc(2, +, -), map_assoc(1, +).
|
||||
|
||||
@@ -220,43 +80,142 @@ have key _Key_.
|
||||
rb_del_max/4
|
||||
]).
|
||||
|
||||
/** @pred empty_assoc(+ _Assoc_)
|
||||
|
||||
Succeeds if association list _Assoc_ is empty.
|
||||
|
||||
*/
|
||||
empty_assoc(t).
|
||||
|
||||
/** @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_)
|
||||
|
||||
Succeeds if _Assoc_ is an association list, that is, if it is a
|
||||
red-black tree.
|
||||
*/
|
||||
is_assoc(t) :- !.
|
||||
is_assoc(T) :-
|
||||
is_rbtree(T).
|
||||
|
||||
/** @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_)
|
||||
|
||||
|
||||
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(+ _Assoc_,? _Key_,? _Value_)
|
||||
|
||||
|
||||
Given the association list _Assoc_, unify _Key_ and _Value_
|
||||
with two associated elements. It can be used to enumerate all elements
|
||||
in the association list.
|
||||
*/
|
||||
gen_assoc(T,K,V) :-
|
||||
rb_in(K,V,T).
|
||||
|
||||
/** @pred get_assoc(+ _Key_,+ _Assoc_,? _Value_)
|
||||
|
||||
|
||||
If _Key_ is one of the elements in the association list _Assoc_,
|
||||
return the associated value.
|
||||
*/
|
||||
get_assoc(K,T,V) :-
|
||||
rb_lookup(K,V,T).
|
||||
|
||||
/** @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).
|
||||
|
||||
/** @pred get_next_assoc(+ _Key_,+ _Assoc_,? _Next_,? _Value_)
|
||||
|
||||
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_)
|
||||
|
||||
|
||||
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_)
|
||||
|
||||
|
||||
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_)
|
||||
|
||||
|
||||
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_)
|
||||
|
||||
|
||||
Succeeds if the unary predicate name _Pred_( _Val_) holds for every
|
||||
element in the association list.
|
||||
|
||||
|
||||
*/
|
||||
map_assoc(t, _) :- !.
|
||||
map_assoc(P, T) :-
|
||||
yap_flag(typein_module, M0),
|
||||
@@ -264,6 +223,12 @@ map_assoc(P, T) :-
|
||||
functor(G, Name, 1),
|
||||
rb_map(T, M:Name).
|
||||
|
||||
/** @pred map_assoc(+ _Pred_,+ _Assoc_,? _New_)
|
||||
|
||||
Given the binary predicate name _Pred_ and the association list
|
||||
_Assoc_, _New_ in an association list with keys in _Assoc_,
|
||||
and such that if _Key-Val_ is in _Assoc_, and _Key-Ans_ is in
|
||||
_New_, then _Pred_( _Val_, _Ans_) holds.*/
|
||||
map_assoc(t, T, T) :- !.
|
||||
map_assoc(P, T, NT) :-
|
||||
yap_flag(typein_module, M0),
|
||||
@@ -277,6 +242,13 @@ 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_)
|
||||
|
||||
The association list _New_ includes and element of association
|
||||
_key_ with _Val_, and all elements of _Assoc_ that did not
|
||||
have key _Key_.
|
||||
|
||||
*/
|
||||
put_assoc(K, T, V, NT) :-
|
||||
rb_update(T, K, V, NT), !.
|
||||
put_assoc(K, t, V, NT) :- !,
|
||||
@@ -284,12 +256,36 @@ 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_)
|
||||
|
||||
|
||||
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_)
|
||||
|
||||
|
||||
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_)
|
||||
|
||||
|
||||
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).
|
||||
|
||||
|
278
library/atts.yap
278
library/atts.yap
@@ -20,264 +20,33 @@
|
||||
%% @{
|
||||
|
||||
/**
|
||||
@defgroup Old_Style_Attribute_Declarations SICStus Prolog style Attribute Declarations
|
||||
@ingroup Attributed_Variables
|
||||
@ingroup Old_Style_Attribute_Declarations
|
||||
|
||||
|
||||
Old style attribute declarations are activated through loading the
|
||||
library <tt>atts</tt> . The command
|
||||
SICStus style attribute declarations are activated through loading the
|
||||
library <tt>atts</tt>. The command
|
||||
|
||||
~~~~~
|
||||
| ?- use_module(library(atts)).
|
||||
~~~~~
|
||||
enables this form of use of attributed variables. The package provides the
|
||||
following functionality:
|
||||
enables this form of attributed variables.
|
||||
|
||||
The directive
|
||||
|
||||
- attribute/1
|
||||
|
||||
and the following user defined predicates can be used:
|
||||
|
||||
- Module:get_atts/2
|
||||
|
||||
- Module:put_atts/2
|
||||
|
||||
- Module:put_atts/3
|
||||
|
||||
- Module:woken_att_do/4
|
||||
|
||||
+ Each attribute must be declared first. Attributes are described by a functor
|
||||
and are declared per module. Each Prolog module declares its own sets of
|
||||
attributes. Different modules may have different functors with the same
|
||||
module.
|
||||
+ The built-in put_atts/2 adds or deletes attributes to a
|
||||
variable. The variable may be unbound or may be an attributed
|
||||
variable. In the latter case, YAP discards previous values for the
|
||||
attributes.
|
||||
+ The built-in get_atts/2 can be used to check the values of
|
||||
an attribute associated with a variable.
|
||||
+ The unification algorithm calls the user-defined predicate
|
||||
<tt>verify_attributes/3</tt> before trying to bind an attributed
|
||||
variable. Unification will resume after this call.
|
||||
+ The user-defined predicate
|
||||
<tt>attribute_goal/2</tt> converts from an attribute to a goal.
|
||||
+ The user-defined predicate
|
||||
<tt>project_attributes/2</tt> is used from a set of variables into a set of
|
||||
constraints or goals. One application of <tt>project_attributes/2</tt> is in
|
||||
the top-level, where it is used to output the set of
|
||||
floundered constraints at the end of a query.
|
||||
*/
|
||||
|
||||
%% @}
|
||||
|
||||
|
||||
%% @{
|
||||
|
||||
/** @defgroup Attribute_Declarations Attribute Declarations
|
||||
@ingroup Old_Style_Attribute_Declarations
|
||||
|
||||
Attributes are compound terms associated with a variable. Each attribute
|
||||
has a <em>name</em> which is <em>private</em> to the module in which the
|
||||
attribute was defined. Variables may have at most one attribute with a
|
||||
name. Attribute names are defined with the following declaration:
|
||||
|
||||
~~~~~
|
||||
:- attribute AttributeSpec, ..., AttributeSpec.
|
||||
~~~~~
|
||||
|
||||
where each _AttributeSpec_ has the form ( _Name_/ _Arity_).
|
||||
One single such declaration is allowed per module _Module_.
|
||||
|
||||
Although the YAP module system is predicate based, attributes are local
|
||||
to modules. This is implemented by rewriting all calls to the
|
||||
built-ins that manipulate attributes so that attribute names are
|
||||
preprocessed depending on the module. The `user:goal_expansion/3`
|
||||
mechanism is used for this purpose.
|
||||
|
||||
|
||||
The attribute manipulation predicates always work as follows:
|
||||
|
||||
+ The first argument is the unbound variable associated with
|
||||
attributes,
|
||||
+ The second argument is a list of attributes. Each attribute will
|
||||
be a Prolog term or a constant, prefixed with the <tt>+</tt> and <tt>-</tt> unary
|
||||
operators. The prefix <tt>+</tt> may be dropped for convenience.
|
||||
|
||||
The following three procedures are available to the user. Notice that
|
||||
these built-ins are rewritten by the system into internal built-ins, and
|
||||
that the rewriting process <em>depends</em> on the module on which the
|
||||
built-ins have been invoked.
|
||||
|
||||
|
||||
The user-predicate predicate verify_attributes/3 is called when
|
||||
attempting to unify an attributed variable which might have attributes
|
||||
in some _Module_.
|
||||
|
||||
|
||||
Attributes are usually presented as goals. The following routines are
|
||||
used by built-in predicates such as call_residue/2 and by the
|
||||
Prolog top-level to display attributes:
|
||||
|
||||
|
||||
Constraint solvers must be able to project a set of constraints to a set
|
||||
of variables. This is useful when displaying the solution to a goal, but
|
||||
may also be used to manipulate computations. The user-defined
|
||||
project_attributes/2 is responsible for implementing this
|
||||
projection.
|
||||
|
||||
|
||||
The following two examples example is taken from the SICStus Prolog manual. It
|
||||
sketches the implementation of a simple finite domain `solver`. Note
|
||||
that an industrial strength solver would have to provide a wider range
|
||||
of functionality and that it quite likely would utilize a more efficient
|
||||
representation for the domains proper. The module exports a single
|
||||
predicate `domain( _-Var_, _?Domain_)` which associates
|
||||
_Domain_ (a list of terms) with _Var_. A variable can be
|
||||
queried for its domain by leaving _Domain_ unbound.
|
||||
|
||||
We do not present here a definition for project_attributes/2.
|
||||
Projecting finite domain constraints happens to be difficult.
|
||||
|
||||
~~~~~
|
||||
:- module(domain, [domain/2]).
|
||||
|
||||
:- use_module(library(atts)).
|
||||
:- use_module(library(ordsets), [
|
||||
ord_intersection/3,
|
||||
ord_intersect/2,
|
||||
list_to_ord_set/2
|
||||
]).
|
||||
|
||||
:- attribute dom/1.
|
||||
|
||||
verify_attributes(Var, Other, Goals) :-
|
||||
get_atts(Var, dom(Da)), !, % are we involved?
|
||||
( var(Other) -> % must be attributed then
|
||||
( get_atts(Other, dom(Db)) -> % has a domain?
|
||||
ord_intersection(Da, Db, Dc),
|
||||
Dc = [El|Els], % at least one element
|
||||
( Els = [] -> % exactly one element
|
||||
Goals = [Other=El] % implied binding
|
||||
; Goals = [],
|
||||
put_atts(Other, dom(Dc))% rescue intersection
|
||||
)
|
||||
; Goals = [],
|
||||
put_atts(Other, dom(Da)) % rescue the domain
|
||||
)
|
||||
; Goals = [],
|
||||
ord_intersect([Other], Da) % value in domain?
|
||||
).
|
||||
verify_attributes(_, _, []). % unification triggered
|
||||
% because of attributes
|
||||
% in other modules
|
||||
|
||||
attribute_goal(Var, domain(Var,Dom)) :- % interpretation as goal
|
||||
get_atts(Var, dom(Dom)).
|
||||
|
||||
domain(X, Dom) :-
|
||||
var(Dom), !,
|
||||
get_atts(X, dom(Dom)).
|
||||
domain(X, List) :-
|
||||
list_to_ord_set(List, Set),
|
||||
Set = [El|Els], % at least one element
|
||||
( Els = [] -> % exactly one element
|
||||
X = El % implied binding
|
||||
; put_atts(Fresh, dom(Set)),
|
||||
X = Fresh % may call
|
||||
% verify_attributes/3
|
||||
).
|
||||
~~~~~
|
||||
|
||||
Note that the _implied binding_ `Other=El` was deferred until after
|
||||
the completion of `verify_attribute/3`. Otherwise, there might be a
|
||||
danger of recursively invoking `verify_attribute/3`, which might bind
|
||||
`Var`, which is not allowed inside the scope of `verify_attribute/3`.
|
||||
Deferring unifications into the third argument of `verify_attribute/3`
|
||||
effectively serializes the calls to `verify_attribute/3`.
|
||||
|
||||
Assuming that the code resides in the file domain.yap, we
|
||||
can use it via:
|
||||
|
||||
~~~~~
|
||||
| ?- use_module(domain).
|
||||
~~~~~
|
||||
|
||||
Let's test it:
|
||||
|
||||
~~~~~
|
||||
| ?- domain(X,[5,6,7,1]), domain(Y,[3,4,5,6]), domain(Z,[1,6,7,8]).
|
||||
|
||||
domain(X,[1,5,6,7]),
|
||||
domain(Y,[3,4,5,6]),
|
||||
domain(Z,[1,6,7,8]) ?
|
||||
|
||||
yes
|
||||
| ?- domain(X,[5,6,7,1]), domain(Y,[3,4,5,6]), domain(Z,[1,6,7,8]),
|
||||
X=Y.
|
||||
|
||||
Y = X,
|
||||
domain(X,[5,6]),
|
||||
domain(Z,[1,6,7,8]) ?
|
||||
|
||||
yes
|
||||
| ?- domain(X,[5,6,7,1]), domain(Y,[3,4,5,6]), domain(Z,[1,6,7,8]),
|
||||
X=Y, Y=Z.
|
||||
|
||||
X = 6,
|
||||
Y = 6,
|
||||
Z = 6
|
||||
~~~~~
|
||||
|
||||
To demonstrate the use of the _Goals_ argument of
|
||||
verify_attributes/3, we give an implementation of
|
||||
freeze/2. We have to name it `myfreeze/2` in order to
|
||||
avoid a name clash with the built-in predicate of the same name.
|
||||
|
||||
~~~~~
|
||||
:- module(myfreeze, [myfreeze/2]).
|
||||
|
||||
:- use_module(library(atts)).
|
||||
|
||||
:- attribute frozen/1.
|
||||
|
||||
verify_attributes(Var, Other, Goals) :-
|
||||
get_atts(Var, frozen(Fa)), !, % are we involved?
|
||||
( var(Other) -> % must be attributed then
|
||||
( get_atts(Other, frozen(Fb)) % has a pending goal?
|
||||
-> put_atts(Other, frozen((Fa,Fb))) % rescue conjunction
|
||||
; put_atts(Other, frozen(Fa)) % rescue the pending goal
|
||||
),
|
||||
Goals = []
|
||||
; Goals = [Fa]
|
||||
).
|
||||
verify_attributes(_, _, []).
|
||||
|
||||
attribute_goal(Var, Goal) :- % interpretation as goal
|
||||
get_atts(Var, frozen(Goal)).
|
||||
|
||||
myfreeze(X, Goal) :-
|
||||
put_atts(Fresh, frozen(Goal)),
|
||||
Fresh = X.
|
||||
~~~~~
|
||||
|
||||
Assuming that this code lives in file myfreeze.yap,
|
||||
we would use it via:
|
||||
|
||||
~~~~~
|
||||
| ?- use_module(myfreeze).
|
||||
| ?- myfreeze(X,print(bound(x,X))), X=2.
|
||||
|
||||
bound(x,2) % side effect
|
||||
X = 2 % bindings
|
||||
~~~~~
|
||||
|
||||
The two solvers even work together:
|
||||
|
||||
~~~~~
|
||||
| ?- myfreeze(X,print(bound(x,X))), domain(X,[1,2,3]),
|
||||
domain(Y,[2,10]), X=Y.
|
||||
|
||||
bound(x,2) % side effect
|
||||
X = 2, % bindings
|
||||
Y = 2
|
||||
~~~~~
|
||||
|
||||
The two example solvers interact via bindings to shared attributed
|
||||
variables only. More complicated interactions are likely to be found
|
||||
in more sophisticated solvers. The corresponding
|
||||
verify_attributes/3 predicates would typically refer to the
|
||||
attributes from other known solvers/modules via the module prefix in
|
||||
` _Module_:get_atts/2`.
|
||||
|
||||
|
||||
*/
|
||||
|
||||
|
||||
:- use_module(library(lists), [member/2]).
|
||||
|
||||
@@ -327,7 +96,7 @@ store_new_module(Mod,Ar,ArgPosition) :-
|
||||
|
||||
:- user_defined_directive(attribute(G), attributes:new_attribute(G)).
|
||||
|
||||
/** @pred _Module_:get_atts( _-Var_, _?ListOfAttributes_)
|
||||
/** @pred Module:get_atts( _-Var_, _?ListOfAttributes_)
|
||||
|
||||
|
||||
Unify the list _?ListOfAttributes_ with the attributes for the unbound
|
||||
@@ -346,7 +115,8 @@ Succeeds if a corresponding attribute is not associated with
|
||||
*/
|
||||
user:goal_expansion(get_atts(Var,AccessSpec), Mod, Goal) :-
|
||||
expand_get_attributes(AccessSpec,Mod,Var,Goal).
|
||||
/** @pred _Module_:put_atts( _-Var_, _?ListOfAttributes_)
|
||||
|
||||
/** @pred Module:put_atts( _-Var_, _?ListOfAttributes_)
|
||||
|
||||
|
||||
Associate with or remove attributes from a variable _Var_. The
|
||||
@@ -473,9 +243,7 @@ find_used([M|Mods],Mods0,L0,Lf) :-
|
||||
find_used([_|Mods],Mods0,L0,Lf) :-
|
||||
find_used(Mods,Mods0,L0,Lf).
|
||||
|
||||
/** @pred _Module_:verify_attributes( _-Var_, _+Value_, _-Goals_)
|
||||
|
||||
|
||||
/** @pred Module:verify_attributes( _-Var_, _+Value_, _-Goals_)
|
||||
|
||||
The predicate is called when trying to unify the attributed variable
|
||||
_Var_ with the Prolog term _Value_. Note that _Value_ may be
|
||||
|
@@ -15,10 +15,39 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
* @file avl.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 00:59:28 2015
|
||||
*
|
||||
* @brief Support for constructing AVL trees
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
/** @defgroup AVL_Trees AVL Trees
|
||||
@ingroup library
|
||||
|
||||
|
||||
:- module(avl, [
|
||||
avl_new/1,
|
||||
avl_insert/4,
|
||||
avl_lookup/3
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup avl AVL Trees
|
||||
* @ingroup library
|
||||
@{
|
||||
Supports constructing AVL trees, available through the directive:
|
||||
|
||||
~~~~~~~
|
||||
:- use_module(library(avl)).
|
||||
~~~~~~~
|
||||
|
||||
It includes the following predicates:
|
||||
|
||||
- avl_insert/4
|
||||
- avl_lookup/3
|
||||
- avl_new/1
|
||||
|
||||
AVL trees are balanced search binary trees. They are named after their
|
||||
inventors, Adelson-Velskii and Landis, and they were the first
|
||||
@@ -34,6 +63,15 @@ you need deletion.
|
||||
*/
|
||||
|
||||
|
||||
/** @pred avl_new(+ _T_)
|
||||
|
||||
|
||||
Create a new tree.
|
||||
|
||||
|
||||
*/
|
||||
avl_new([]).
|
||||
|
||||
/** @pred avl_insert(+ _Key_,? _Value_,+ _T0_,- _TF_)
|
||||
|
||||
|
||||
@@ -43,31 +81,6 @@ allowed.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred avl_lookup(+ _Key_,- _Value_,+ _T_)
|
||||
|
||||
|
||||
Lookup an element with key _Key_ in the AVL tree
|
||||
_T_, returning the value _Value_.
|
||||
|
||||
|
||||
|
||||
|
||||
*/
|
||||
/** @pred avl_new(+ _T_)
|
||||
|
||||
|
||||
Create a new tree.
|
||||
|
||||
|
||||
*/
|
||||
:- module(avl, [
|
||||
avl_new/1,
|
||||
avl_insert/4,
|
||||
avl_lookup/3
|
||||
]).
|
||||
|
||||
avl_new([]).
|
||||
|
||||
avl_insert(Key, Value, T0, TF) :-
|
||||
insert(T0, Key, Value, TF, _).
|
||||
|
||||
@@ -115,6 +128,13 @@ table2(< ,- ,> ).
|
||||
table2(> ,< ,- ).
|
||||
table2(- ,- ,- ).
|
||||
|
||||
/** @pred avl_lookup(+ _Key_,- _Value_,+ _T_)
|
||||
|
||||
|
||||
Lookup an element with key _Key_ in the AVL tree
|
||||
_T_, returning the value _Value_.
|
||||
|
||||
*/
|
||||
|
||||
avl_lookup(Key, Value, avl(L,Key0,KVal,_,R)) :-
|
||||
compare(Cmp, Key, Key0),
|
||||
|
@@ -1,17 +1,15 @@
|
||||
%% -*- Prolog -*-
|
||||
|
||||
/*
|
||||
|
||||
@defgroup YapHash Backtrackable Hash Tables
|
||||
@ingroup YapLibrary
|
||||
@{
|
||||
|
||||
This code implements hash-arrays.
|
||||
It requires the hash key to be a ground term.
|
||||
|
||||
It relies on dynamic array code.
|
||||
|
||||
/**
|
||||
* @file bhash.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 01:11:29 2015
|
||||
*
|
||||
* @brief Backtrackable Hash Tables
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- source.
|
||||
:- yap_flag(unknown,error).
|
||||
:- style_check(all).
|
||||
@@ -32,6 +30,21 @@ It relies on dynamic array code.
|
||||
b_hash_keys_to_list/2
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup bhash Backtrackable Hash Tables
|
||||
* @ingroup library
|
||||
|
||||
This library implements hash-arrays.
|
||||
It requires the hash key to be a ground term. The library can
|
||||
be loaded as
|
||||
|
||||
:- use_module( library( bhash ) ).
|
||||
|
||||
This code relies on backtrackable updates. The default hash key is
|
||||
generated by term_hash/4.
|
||||
|
||||
*/
|
||||
|
||||
:- use_module(library(terms), [ term_hash/4 ]).
|
||||
|
||||
|
||||
@@ -313,5 +326,4 @@ mklistvals(K.Vals, KK.NVals) :-
|
||||
mklistvals(Vals, NVals).
|
||||
|
||||
/**
|
||||
@}
|
||||
*/
|
||||
|
@@ -1,5 +1,15 @@
|
||||
%%% -*- Mode: Prolog; -*-
|
||||
|
||||
/**
|
||||
* @file block_diagram.yap
|
||||
* @author Theofrastos Mantadelis, Sugestions from Paulo Moura
|
||||
* @date Tue Nov 17 14:12:02 2015
|
||||
*
|
||||
* @brief Graph the program structure.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% Flags was developed at Katholieke Universiteit Leuven
|
||||
@@ -201,7 +211,7 @@
|
||||
%
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
/** @defgroup Block_Diagram Block Diagram
|
||||
/** @defgroup block_diagram Block Diagram
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
|
@@ -1,4 +1,13 @@
|
||||
%%% -*- Mode: Prolog; -*-
|
||||
/**
|
||||
* @file c_alarms.yap
|
||||
* @author Theofrastos Mantadelis
|
||||
* @date Tue Nov 17 14:50:03 2015
|
||||
*
|
||||
* @brief Concurrent alarms
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
@@ -210,7 +219,7 @@
|
||||
timer_elapsed/2,
|
||||
timer_pause/2]).
|
||||
|
||||
/** @defgroup CAlarms Concurrent Alarms
|
||||
/** @defgroup c_alarms Concurrent Alarms
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
|
@@ -15,6 +15,17 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
* @file charsio.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 01:17:33 2015
|
||||
*
|
||||
* @brief Several operations on text.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(charsio, [
|
||||
format_to_chars/3,
|
||||
format_to_chars/4,
|
||||
@@ -32,10 +43,33 @@
|
||||
term_to_atom/2
|
||||
]).
|
||||
|
||||
/** @defgroup CharsIO Operations on Sequences of Codes.
|
||||
/** @defgroup charsio Operations on Sequences of Codes.
|
||||
@ingroup library
|
||||
|
||||
Term to sequence of codes conversion, mostly replaced by engine code.
|
||||
You can use the following directive to load the files.
|
||||
|
||||
|
||||
~~~~~~~
|
||||
:- use_module(library(avl)).
|
||||
~~~~~~~
|
||||
|
||||
It includes the following predicates:
|
||||
- atom_to_chars/2
|
||||
- atom_to_chars/3
|
||||
- format_to_chars/3
|
||||
- format_to_chars/4
|
||||
- number_to_chars/2
|
||||
- number_to_chars/3
|
||||
- open_chars_stream/2
|
||||
- read_from_chars/2
|
||||
- term_to_atom/2
|
||||
- with_output_to_chars/2
|
||||
- with_output_to_chars/3
|
||||
- with_output_to_chars/4
|
||||
- write_to_chars/2
|
||||
- write_to_chars/3
|
||||
|
||||
*/
|
||||
|
||||
:- meta_predicate(with_output_to_chars(0,?)).
|
||||
@@ -184,8 +218,8 @@ a dot character such that either (i) the dot character is followed by
|
||||
blank characters; or (ii) the dot character is the last character in the
|
||||
string.
|
||||
|
||||
% @compat The SWI-Prolog version does not require Codes to end
|
||||
% in a full-stop.
|
||||
@compat The SWI-Prolog version does not require Codes to end
|
||||
in a full-stop.
|
||||
*/
|
||||
read_from_chars("", end_of_file) :- !.
|
||||
read_from_chars(List, Term) :-
|
||||
|
@@ -1,3 +1,12 @@
|
||||
/**
|
||||
* @file clauses.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 14:51:30 2015
|
||||
*
|
||||
* @brief Utilities for clause manipulation.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(clauses,
|
||||
[list2conj/2,
|
||||
@@ -7,9 +16,8 @@
|
||||
%%! @{
|
||||
|
||||
/**
|
||||
@file clauses.yap
|
||||
@defgroup clauses Clause Manipulation
|
||||
@ingroup library
|
||||
* @defgroup clauses Clause Manipulation
|
||||
* @ingroup library
|
||||
|
||||
This library supports a number of useful utilities that come up over and
|
||||
over again when manipulating Prolog programs. This will include
|
||||
|
@@ -1,3 +1,12 @@
|
||||
/**
|
||||
* @file cleanup.yap
|
||||
* @author Christian Thaeter
|
||||
* @date Tue Nov 17 14:52:58 2015
|
||||
*
|
||||
* @brief old implementation of call_cleanup
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module( cleanup, [
|
||||
@@ -8,7 +17,7 @@
|
||||
op(1150, fx,fragile)
|
||||
]).
|
||||
|
||||
%% @defgroup Cleanup Call Cleanup
|
||||
%% @defgroup cleanup Old Call Cleanup
|
||||
% @ingroup library
|
||||
% @{
|
||||
%
|
||||
|
@@ -1,3 +1,16 @@
|
||||
/**
|
||||
* @file coinduction.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>, Arvin Bansal,
|
||||
*
|
||||
*
|
||||
* @date Tue Nov 17 14:55:02 2015
|
||||
*
|
||||
* @brief Co-inductive execution
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
/*************************************************************************
|
||||
* *
|
||||
* YAP Prolog *
|
||||
@@ -30,7 +43,7 @@
|
||||
|
||||
:- use_module(library(error)).
|
||||
|
||||
/** <module> Co-Logic Programming
|
||||
/** <module> coinduction Co-Logic Programming
|
||||
@ingroup library
|
||||
|
||||
This simple module implements the directive coinductive/1 as described
|
||||
|
@@ -1,13 +1,14 @@
|
||||
/**
|
||||
@defgroup DBQUeue Non-baacktrackable queues in YAP.
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
A library to implement queues of NB Terms
|
||||
|
||||
@{
|
||||
* @file dbqueues.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 15:01:49 2015
|
||||
*
|
||||
* @brief A library to support queues with no-backtrackable queues.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(nbqueue, [
|
||||
nb_enqueue/2,
|
||||
nb_dequeue/2,
|
||||
@@ -15,6 +16,14 @@ A library to implement queues of NB Terms
|
||||
nb_size/2
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup dbqueues Non-backtrackable queues in YAP.
|
||||
* @ingroup library
|
||||
|
||||
A library to implement queues of NB Terms
|
||||
|
||||
*/
|
||||
|
||||
|
||||
:- unhide('$init_nb_queue').
|
||||
:- unhide('$nb_enqueue').
|
||||
@@ -59,6 +68,3 @@ nb_dequeue_all(Ref) :-
|
||||
nb_dequeue_size(Ref, Size) :-
|
||||
prolog:'$nb_size'(Ref, Size).
|
||||
|
||||
/**
|
||||
@}
|
||||
*/
|
@@ -1,12 +1,11 @@
|
||||
|
||||
/**
|
||||
@defgroup DBUsage Memory Usage in Prolog Data-Base
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
This library provides a set of utilities for studying memory usage in YAP.
|
||||
The following routines are available once included with the
|
||||
`use_module(library(dbusage))` command.
|
||||
* @file dbusage.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 15:04:52 2015
|
||||
*
|
||||
* @brief Useful statistics on memory usage
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(dbusage, [
|
||||
@@ -17,6 +16,16 @@
|
||||
db_dynamic/1
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup dbusage Memory Usage in Prolog Data-Base
|
||||
* @ingroup library
|
||||
@{
|
||||
|
||||
This library provides a set of utilities for studying memory usage in YAP.
|
||||
The following routines are available once included with the
|
||||
`use_module(library(dbusage))` command.
|
||||
*/
|
||||
|
||||
/** @pred db_usage
|
||||
Give general overview of data-base usage in the system.
|
||||
*/
|
||||
|
@@ -1,280 +1,13 @@
|
||||
% File : dgraphs.yap
|
||||
% Author : Vitor Santos Costa
|
||||
% Updated: 2006
|
||||
% Purpose: Directed Graph Processing Utilities.
|
||||
|
||||
|
||||
/** @defgroup DGraphs Directed Graphs
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
The following graph manipulation routines use the red-black tree library
|
||||
to try to avoid linear-time scans of the graph for all graph
|
||||
operations. Graphs are represented as a red-black tree, where the key is
|
||||
the vertex, and the associated value is a list of vertices reachable
|
||||
from that vertex through an edge (ie, a list of edges).
|
||||
|
||||
|
||||
|
||||
@pred dgraph_new(+ _Graph_)
|
||||
|
||||
|
||||
Create a new directed graph. This operation must be performed before
|
||||
trying to use the graph.
|
||||
|
||||
|
||||
/**
|
||||
* @file dgraphs.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 01:23:20 2015
|
||||
*
|
||||
* @brief Directed Graph Processing Utilities.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
/** @pred dgraph_add_edge(+ _Graph_, + _N1_, + _N2_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by adding the edge
|
||||
_N1_- _N2_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_add_edges(+ _Graph_, + _Edges_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by adding the list of
|
||||
edges _Edges_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_add_vertices(+ _Graph_, + _Vertex_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by adding
|
||||
vertex _Vertex_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_add_vertices(+ _Graph_, + _Vertices_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by adding the list of
|
||||
vertices _Vertices_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_complement(+ _Graph_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with the graph complementary to _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_compose(+ _Graph1_, + _Graph2_, - _ComposedGraph_)
|
||||
|
||||
|
||||
Unify _ComposedGraph_ with a new graph obtained by composing
|
||||
_Graph1_ and _Graph2_, ie, _ComposedGraph_ has an edge
|
||||
_V1-V2_ iff there is a _V_ such that _V1-V_ in _Graph1_
|
||||
and _V-V2_ in _Graph2_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_del_edge(+ _Graph_, + _N1_, + _N2_, - _NewGraph_)
|
||||
|
||||
|
||||
Succeeds if _NewGraph_ unifies with a new graph obtained by
|
||||
removing the edge _N1_- _N2_ from the graph _Graph_. Notice
|
||||
that no vertices are deleted.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_del_edges(+ _Graph_, + _Edges_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by removing the list of
|
||||
edges _Edges_ from the graph _Graph_. Notice that no vertices
|
||||
are deleted.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_del_vertex(+ _Graph_, + _Vertex_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by deleting vertex
|
||||
_Vertex_ and all the edges that start from or go to _Vertex_ to
|
||||
the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_del_vertices(+ _Graph_, + _Vertices_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by deleting the list of
|
||||
vertices _Vertices_ and all the edges that start from or go to a
|
||||
vertex in _Vertices_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_edge(+ _N1_, + _N2_, + _Graph_)
|
||||
|
||||
|
||||
Edge _N1_- _N2_ is an edge in directed graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_edges(+ _Graph_, - _Edges_)
|
||||
|
||||
|
||||
Unify _Edges_ with all edges appearing in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_isomorphic(+ _Vs_, + _NewVs_, + _G0_, - _GF_)
|
||||
|
||||
|
||||
Unify the list _GF_ with the graph isomorphic to _G0_ where
|
||||
vertices in _Vs_ map to vertices in _NewVs_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_leaves(+ _Graph_, ? _Vertices_)
|
||||
|
||||
|
||||
The vertices _Vertices_ have no outgoing edge in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_max_path(+ _V1_, + _V1_, + _Graph_, - _Path_, ? _Costt_)
|
||||
|
||||
|
||||
Unify the list _Path_ with the maximal cost path between nodes
|
||||
_N1_ and _N2_ in graph _Graph_. Path _Path_ has cost
|
||||
_Cost_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_min_path(+ _V1_, + _V1_, + _Graph_, - _Path_, ? _Costt_)
|
||||
|
||||
|
||||
Unify the list _Path_ with the minimal cost path between nodes
|
||||
_N1_ and _N2_ in graph _Graph_. Path _Path_ has cost
|
||||
_Cost_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_min_paths(+ _V1_, + _Graph_, - _Paths_)
|
||||
|
||||
|
||||
Unify the list _Paths_ with the minimal cost paths from node
|
||||
_N1_ to the nodes in graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_neighbors(+ _Vertex_, + _Graph_, - _Vertices_)
|
||||
|
||||
|
||||
Unify _Vertices_ with the list of neighbors of vertex _Vertex_
|
||||
in _Graph_. If the vertice is not in the graph fail.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_neighbours(+ _Vertex_, + _Graph_, - _Vertices_)
|
||||
|
||||
|
||||
Unify _Vertices_ with the list of neighbours of vertex _Vertex_
|
||||
in _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_path(+ _Vertex_, + _Graph_, ? _Path_)
|
||||
|
||||
|
||||
The path _Path_ is a path starting at vertex _Vertex_ in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_path(+ _Vertex_, + _Vertex1_, + _Graph_, ? _Path_)
|
||||
|
||||
The path _Path_ is a path starting at vertex _Vertex_ in graph
|
||||
_Graph_ and ending at path _Vertex2_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_reachable(+ _Vertex_, + _Graph_, ? _Edges_)
|
||||
|
||||
|
||||
The path _Path_ is a path starting at vertex _Vertex_ in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_symmetric_closure(+ _Graph_, - _Closure_)
|
||||
|
||||
|
||||
Unify _Closure_ with the symmetric closure of graph _Graph_,
|
||||
that is, if _Closure_ contains an edge _U-V_ it must also
|
||||
contain the edge _V-U_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_to_ugraph(+ _Graph_, - _UGraph_)
|
||||
|
||||
|
||||
Unify _UGraph_ with the representation used by the _ugraphs_
|
||||
unweighted graphs library, that is, a list of the form
|
||||
_V-Neighbors_, where _V_ is a node and _Neighbors_ the nodes
|
||||
children.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_top_sort(+ _Graph_, - _Vertices_)
|
||||
|
||||
|
||||
Unify _Vertices_ with the topological sort of graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_top_sort(+ _Graph_, - _Vertices_, ? _Vertices0_)
|
||||
|
||||
Unify the difference list _Vertices_- _Vertices0_ with the
|
||||
topological sort of graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_transitive_closure(+ _Graph_, - _Closure_)
|
||||
|
||||
|
||||
Unify _Closure_ with the transitive closure of graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_transpose(+ _Graph_, - _Transpose_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained from _Graph_ by
|
||||
replacing all edges of the form _V1-V2_ by edges of the form
|
||||
_V2-V1_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred dgraph_vertices(+ _Graph_, - _Vertices_)
|
||||
|
||||
|
||||
Unify _Vertices_ with all vertices appearing in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred ugraph_to_dgraph( + _UGraph_, - _Graph_)
|
||||
|
||||
|
||||
Unify _Graph_ with the directed graph obtain from _UGraph_,
|
||||
represented in the form used in the _ugraphs_ unweighted graphs
|
||||
library.
|
||||
|
||||
|
||||
*/
|
||||
:- module( dgraphs,
|
||||
[
|
||||
dgraph_vertices/2,
|
||||
@@ -307,8 +40,29 @@ library.
|
||||
dgraph_path/4,
|
||||
dgraph_leaves/2,
|
||||
dgraph_reachable/3
|
||||
]).
|
||||
]).
|
||||
|
||||
/** @defgroup dgraphs Directed Graphs
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
The following graph manipulation routines use the red-black tree library
|
||||
to try to avoid linear-time scans of the graph for all graph
|
||||
operations. Graphs are represented as a red-black tree, where the key is
|
||||
the vertex, and the associated value is a list of vertices reachable
|
||||
from that vertex through an edge (ie, a list of edges).
|
||||
|
||||
*/
|
||||
|
||||
|
||||
/** @pred dgraph_new(+ _Graph_)
|
||||
|
||||
|
||||
Create a new directed graph. This operation must be performed before
|
||||
trying to use the graph.
|
||||
|
||||
|
||||
*/
|
||||
:- reexport(library(rbtrees),
|
||||
[rb_new/1 as dgraph_new]).
|
||||
|
||||
@@ -338,10 +92,28 @@ library.
|
||||
wdgraph_max_path/5,
|
||||
wdgraph_min_paths/3]).
|
||||
|
||||
|
||||
/** @pred dgraph_add_edge(+ _Graph_, + _N1_, + _N2_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by adding the edge
|
||||
_N1_- _N2_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_add_edge(Vs0,V1,V2,Vs2) :-
|
||||
dgraph_new_edge(V1,V2,Vs0,Vs1),
|
||||
dgraph_add_vertex(Vs1,V2,Vs2).
|
||||
|
||||
|
||||
/** @pred dgraph_add_edges(+ _Graph_, + _Edges_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by adding the list of
|
||||
edges _Edges_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_add_edges(V0, Edges, VF) :-
|
||||
rb_empty(V0), !,
|
||||
sort(Edges,SortedEdges),
|
||||
@@ -397,21 +169,52 @@ dgraph_new_edge(V1,V2,Vs0,Vs) :-
|
||||
insert_edge(V2, Children0, Children) :-
|
||||
ord_insert(Children0,V2,Children).
|
||||
|
||||
/** @pred dgraph_add_vertices(+ _Graph_, + _Vertices_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by adding the list of
|
||||
vertices _Vertices_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_add_vertices(G, [], G).
|
||||
dgraph_add_vertices(G0, [V|Vs], GF) :-
|
||||
dgraph_add_vertex(G0, V, G1),
|
||||
dgraph_add_vertices(G1, Vs, GF).
|
||||
|
||||
|
||||
/** @pred dgraph_add_vertex(+ _Graph_, + _Vertex_, - _NewGraph_)
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by adding
|
||||
vertex _Vertex_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_add_vertex(Vs0, V, Vs0) :-
|
||||
rb_lookup(V,_,Vs0), !.
|
||||
dgraph_add_vertex(Vs0, V, Vs) :-
|
||||
rb_insert(Vs0, V, [], Vs).
|
||||
|
||||
|
||||
/** @pred dgraph_edges(+ _Graph_, - _Edges_)
|
||||
|
||||
|
||||
Unify _Edges_ with all edges appearing in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_edges(Vs,Edges) :-
|
||||
rb_visit(Vs,L0),
|
||||
cvt2edges(L0,Edges).
|
||||
|
||||
/** @pred dgraph_vertices(+ _Graph_, - _Vertices_)
|
||||
|
||||
|
||||
Unify _Vertices_ with all vertices appearing in graph
|
||||
_Graph_.
|
||||
|
||||
*/
|
||||
dgraph_vertices(Vs,Vertices) :-
|
||||
rb_keys(Vs,Vertices).
|
||||
|
||||
@@ -424,8 +227,25 @@ children2edges([],_,Edges,Edges).
|
||||
children2edges([Child|L0],V,[V-Child|EdgesF],Edges0) :-
|
||||
children2edges(L0,V,EdgesF,Edges0).
|
||||
|
||||
/** @pred dgraph_neighbours(+ _Vertex_, + _Graph_, - _Vertices_)
|
||||
|
||||
|
||||
Unify _Vertices_ with the list of neighbours of vertex _Vertex_
|
||||
in _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_neighbours(V,Vertices,Children) :-
|
||||
rb_lookup(V,Children,Vertices).
|
||||
|
||||
/** @pred dgraph_neighbors(+ _Vertex_, + _Graph_, - _Vertices_)
|
||||
|
||||
|
||||
Unify _Vertices_ with the list of neighbors of vertex _Vertex_
|
||||
in _Graph_. If the vertice is not in the graph fail.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_neighbors(V,Vertices,Children) :-
|
||||
rb_lookup(V,Children,Vertices).
|
||||
|
||||
@@ -434,7 +254,13 @@ add_vertices(Graph, [V|Vertices], NewGraph) :-
|
||||
rb_insert(Graph, V, [], IntGraph),
|
||||
add_vertices(IntGraph, Vertices, NewGraph).
|
||||
|
||||
/** @pred dgraph_complement(+ _Graph_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with the graph complementary to _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_complement(Vs0,VsF) :-
|
||||
dgraph_vertices(Vs0,Vertices),
|
||||
rb_map(Vs0,complement(Vertices),VsF).
|
||||
@@ -442,9 +268,27 @@ dgraph_complement(Vs0,VsF) :-
|
||||
complement(Vs,Children,NewChildren) :-
|
||||
ord_subtract(Vs,Children,NewChildren).
|
||||
|
||||
/** @pred dgraph_del_edge(+ _Graph_, + _N1_, + _N2_, - _NewGraph_)
|
||||
|
||||
|
||||
Succeeds if _NewGraph_ unifies with a new graph obtained by
|
||||
removing the edge _N1_- _N2_ from the graph _Graph_. Notice
|
||||
that no vertices are deleted.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_del_edge(Vs0,V1,V2,Vs1) :-
|
||||
rb_apply(Vs0, V1, delete_edge(V2), Vs1).
|
||||
|
||||
/** @pred dgraph_del_edges(+ _Graph_, + _Edges_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by removing the list of
|
||||
edges _Edges_ from the graph _Graph_. Notice that no vertices
|
||||
are deleted.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_del_edges(G0, Edges, Gf) :-
|
||||
sort(Edges,SortedEdges),
|
||||
continue_del_edges(SortedEdges, G0, Gf).
|
||||
@@ -461,6 +305,15 @@ contract_vertex(V,Children, Vs0, Vs) :-
|
||||
del_edges(ToRemove,E0,E) :-
|
||||
ord_subtract(E0,ToRemove,E).
|
||||
|
||||
/** @pred dgraph_del_vertex(+ _Graph_, + _Vertex_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by deleting vertex
|
||||
_Vertex_ and all the edges that start from or go to _Vertex_ to
|
||||
the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_del_vertex(Vs0, V, Vsf) :-
|
||||
rb_delete(Vs0, V, Vs1),
|
||||
rb_map(Vs1, delete_edge(V), Vsf).
|
||||
@@ -468,6 +321,15 @@ dgraph_del_vertex(Vs0, V, Vsf) :-
|
||||
delete_edge(Edges0, V, Edges) :-
|
||||
ord_del_element(Edges0, V, Edges).
|
||||
|
||||
/** @pred dgraph_del_vertices(+ _Graph_, + _Vertices_, - _NewGraph_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained by deleting the list of
|
||||
vertices _Vertices_ and all the edges that start from or go to a
|
||||
vertex in _Vertices_ to the graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_del_vertices(G0, Vs, GF) :-
|
||||
sort(Vs,SortedVs),
|
||||
delete_all(SortedVs, G0, G1),
|
||||
@@ -483,6 +345,15 @@ delete_all([V|Vs],Vs0,Vsf) :-
|
||||
delete_remaining_edges(SortedVs,Vs0,Vsf) :-
|
||||
rb_map(Vs0, del_edges(SortedVs), Vsf).
|
||||
|
||||
/** @pred dgraph_transpose(+ _Graph_, - _Transpose_)
|
||||
|
||||
|
||||
Unify _NewGraph_ with a new graph obtained from _Graph_ by
|
||||
replacing all edges of the form _V1-V2_ by edges of the form
|
||||
_V2-V1_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_transpose(Graph, TGraph) :-
|
||||
rb_visit(Graph, Edges),
|
||||
transpose(Edges, Nodes, TEdges, []),
|
||||
@@ -522,6 +393,13 @@ compose3([], _, NewNodes, NewNodes).
|
||||
compose3([GC|GrandChildren], V, [V-GC|NewNodes], NewNodes0) :-
|
||||
compose3(GrandChildren, V, NewNodes, NewNodes0).
|
||||
|
||||
/** @pred dgraph_transitive_closure(+ _Graph_, - _Closure_)
|
||||
|
||||
|
||||
Unify _Closure_ with the transitive closure of graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_transitive_closure(G,Closure) :-
|
||||
dgraph_edges(G,Edges),
|
||||
continue_closure(Edges,G,Closure).
|
||||
@@ -549,6 +427,15 @@ is_edge(V1,V2,G) :-
|
||||
rb_lookup(V1,Children,G),
|
||||
ord_memberchk(V2, Children).
|
||||
|
||||
/** @pred dgraph_symmetric_closure(+ _Graph_, - _Closure_)
|
||||
|
||||
|
||||
Unify _Closure_ with the symmetric closure of graph _Graph_,
|
||||
that is, if _Closure_ contains an edge _U-V_ it must also
|
||||
contain the edge _V-U_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_symmetric_closure(G,S) :-
|
||||
dgraph_edges(G, Edges),
|
||||
invert_edges(Edges, InvertedEdges),
|
||||
@@ -558,9 +445,23 @@ invert_edges([], []).
|
||||
invert_edges([V1-V2|Edges], [V2-V1|InvertedEdges]) :-
|
||||
invert_edges(Edges, InvertedEdges).
|
||||
|
||||
/** @pred dgraph_top_sort(+ _Graph_, - _Vertices_)
|
||||
|
||||
|
||||
Unify _Vertices_ with the topological sort of graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_top_sort(G, Q) :-
|
||||
dgraph_top_sort(G, Q, []).
|
||||
|
||||
/** @pred dgraph_top_sort(+ _Graph_, - _Vertices_, ? _Vertices0_)
|
||||
|
||||
Unify the difference list _Vertices_- _Vertices0_ with the
|
||||
topological sort of graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_top_sort(G, Q, RQ0) :-
|
||||
% O(E)
|
||||
rb_visit(G, Vs),
|
||||
@@ -611,30 +512,85 @@ close_links([l(V,A,A,S,E)|Links], RQ, RQ0) :-
|
||||
( S == E -> RQ = [V| RQ1] ; RQ = RQ1),
|
||||
close_links(Links, RQ1, RQ0).
|
||||
|
||||
/** @pred ugraph_to_dgraph( + _UGraph_, - _Graph_)
|
||||
|
||||
|
||||
Unify _Graph_ with the directed graph obtain from _UGraph_,
|
||||
represented in the form used in the _ugraphs_ unweighted graphs
|
||||
library.
|
||||
|
||||
*/
|
||||
ugraph_to_dgraph(UG, DG) :-
|
||||
ord_list_to_rbtree(UG, DG).
|
||||
|
||||
/** @pred dgraph_to_ugraph(+ _Graph_, - _UGraph_)
|
||||
|
||||
|
||||
Unify _UGraph_ with the representation used by the _ugraphs_
|
||||
unweighted graphs library, that is, a list of the form
|
||||
_V-Neighbors_, where _V_ is a node and _Neighbors_ the nodes
|
||||
children.
|
||||
|
||||
*/
|
||||
dgraph_to_ugraph(DG, UG) :-
|
||||
rb_visit(DG, UG).
|
||||
|
||||
/** @pred dgraph_edge(+ _N1_, + _N2_, + _Graph_)
|
||||
|
||||
|
||||
Edge _N1_- _N2_ is an edge in directed graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_edge(N1, N2, G) :-
|
||||
rb_lookup(N1, Ns, G),
|
||||
ord_memberchk(N2, Ns).
|
||||
|
||||
/** @pred dgraph_min_path(+ _V1_, + _V1_, + _Graph_, - _Path_, ? _Costt_)
|
||||
|
||||
|
||||
Unify the list _Path_ with the minimal cost path between nodes
|
||||
_N1_ and _N2_ in graph _Graph_. Path _Path_ has cost
|
||||
_Cost_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_min_path(V1, V2, Graph, Path, Cost) :-
|
||||
dgraph_to_wdgraph(Graph, WGraph),
|
||||
wdgraph_min_path(V1, V2, WGraph, Path, Cost).
|
||||
|
||||
/** @pred dgraph_max_path(+ _V1_, + _V1_, + _Graph_, - _Path_, ? _Costt_)
|
||||
|
||||
|
||||
Unify the list _Path_ with the maximal cost path between nodes
|
||||
_N1_ and _N2_ in graph _Graph_. Path _Path_ has cost
|
||||
_Cost_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_max_path(V1, V2, Graph, Path, Cost) :-
|
||||
dgraph_to_wdgraph(Graph, WGraph),
|
||||
wdgraph_max_path(V1, V2, WGraph, Path, Cost).
|
||||
|
||||
/** @pred dgraph_min_paths(+ _V1_, + _Graph_, - _Paths_)
|
||||
|
||||
|
||||
Unify the list _Paths_ with the minimal cost paths from node
|
||||
_N1_ to the nodes in graph _Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_min_paths(V1, Graph, Paths) :-
|
||||
dgraph_to_wdgraph(Graph, WGraph),
|
||||
wdgraph_min_paths(V1, WGraph, Paths).
|
||||
|
||||
/** @pred dgraph_path(+ _Vertex_, + _Vertex1_, + _Graph_, ? _Path_)
|
||||
|
||||
The path _Path_ is a path starting at vertex _Vertex_ in graph
|
||||
_Graph_ and ending at path _Vertex2_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_path(V1, V2, Graph, Path) :-
|
||||
rb_new(E0),
|
||||
rb_lookup(V1, Children, Graph),
|
||||
@@ -663,12 +619,28 @@ do_children([V|_], G, SoFar, [V|Path]) :-
|
||||
do_children([_|Children], G, SoFar, Path) :-
|
||||
do_children(Children, G, SoFar, Path).
|
||||
|
||||
/** @pred dgraph_path(+ _Vertex_, + _Graph_, ? _Path_)
|
||||
|
||||
|
||||
The path _Path_ is a path starting at vertex _Vertex_ in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_path(V, G, [V|P]) :-
|
||||
rb_lookup(V, Children, G),
|
||||
ord_del_element(Children, V, Ch),
|
||||
do_path(Ch, G, [V], P).
|
||||
|
||||
|
||||
/** @pred dgraph_isomorphic(+ _Vs_, + _NewVs_, + _G0_, - _GF_)
|
||||
|
||||
|
||||
Unify the list _GF_ with the graph isomorphic to _G0_ where
|
||||
vertices in _Vs_ map to vertices in _NewVs_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_isomorphic(Vs, Vs2, G1, G2) :-
|
||||
rb_new(Map0),
|
||||
mapping(Vs,Vs2,Map0,Map),
|
||||
@@ -691,6 +663,14 @@ translate_edges([V1-V2|Edges],Map,[NV1-NV2|TEdges]) :-
|
||||
rb_lookup(V2,NV2,Map),
|
||||
translate_edges(Edges,Map,TEdges).
|
||||
|
||||
/** @pred dgraph_reachable(+ _Vertex_, + _Graph_, ? _Edges_)
|
||||
|
||||
|
||||
The path _Path_ is a path starting at vertex _Vertex_ in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_reachable(V, G, Edges) :-
|
||||
rb_lookup(V, Children, G),
|
||||
ord_list_to_rbtree([V-[]],Done0),
|
||||
@@ -706,6 +686,14 @@ reachable([V|Vertices], Done0, DoneF, G, [V|EdgesF], Edges0) :-
|
||||
reachable(Kids, Done1, DoneI, G, EdgesF, EdgesI),
|
||||
reachable(Vertices, DoneI, DoneF, G, EdgesI, Edges0).
|
||||
|
||||
/** @pred dgraph_leaves(+ _Graph_, ? _Vertices_)
|
||||
|
||||
|
||||
The vertices _Vertices_ have no outgoing edge in graph
|
||||
_Graph_.
|
||||
|
||||
|
||||
*/
|
||||
dgraph_leaves(Graph, Vertices) :-
|
||||
rb_visit(Graph, Pairs),
|
||||
vertices_without_children(Pairs, Vertices).
|
||||
|
@@ -151,7 +151,7 @@ that concatenated give _A12_.
|
||||
|
||||
goal_expansion(atom_concat(A,B,C),atomic_concat(A,B,C)).
|
||||
%goal_expansion(arg(A,_,_),_) :- nonvar(A), !, fail.
|
||||
goal_expansion(arg(A,B,C),genarg(A,B,C)).
|
||||
goal_expansion(arg(A,B,C),arg:genarg(A,B,C)).
|
||||
|
||||
% make sure we also use
|
||||
:- user:library_directory(X),
|
||||
|
@@ -1,13 +1,39 @@
|
||||
% This file has been included as an YAP library by Vitor Santos Costa, 2013
|
||||
|
||||
% it implements a very simple interval solver designed to interact with the exo
|
||||
% data-base.
|
||||
% It assumes simple queries and a contiguous interval,
|
||||
% and does not really expect to do non-trivial
|
||||
% constraint propagation and solving.
|
||||
/**
|
||||
* @file exo_interval.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date 2013
|
||||
*
|
||||
* @brief This file implements a very simple interval solver
|
||||
* designed to interact with the exo
|
||||
* data-base.
|
||||
* It assumes simple queries and a contiguous interval,
|
||||
* and does not really expect to do non-trivial
|
||||
* constraint propagation and solving.
|
||||
*
|
||||
*
|
||||
*/
|
||||
:- module(exo_interval,
|
||||
[max/2,
|
||||
min/2,
|
||||
any/2,
|
||||
max/1,
|
||||
min/1,
|
||||
maximum/1,
|
||||
minimum/1,
|
||||
any/1,
|
||||
(#<)/2,
|
||||
(#>)/2,
|
||||
(#=<)/2,
|
||||
(#>=)/2,
|
||||
(#=)/2,
|
||||
op(700, xfx, (#>)),
|
||||
op(700, xfx, (#<)),
|
||||
op(700, xfx, (#>=)),
|
||||
op(700, xfx, (#=<)),
|
||||
op(700, xfx, (#=))]).
|
||||
|
||||
|
||||
/** @defgroup Exo_Intervals Exo Intervals
|
||||
/** @defgroup exo_interval Exo Intervals
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -73,26 +99,6 @@ infimum.
|
||||
|
||||
|
||||
*/
|
||||
:- module(exo_interval,
|
||||
[max/2,
|
||||
min/2,
|
||||
any/2,
|
||||
max/1,
|
||||
min/1,
|
||||
maximum/1,
|
||||
minimum/1,
|
||||
any/1,
|
||||
(#<)/2,
|
||||
(#>)/2,
|
||||
(#=<)/2,
|
||||
(#>=)/2,
|
||||
(#=)/2,
|
||||
op(700, xfx, (#>)),
|
||||
op(700, xfx, (#<)),
|
||||
op(700, xfx, (#>=)),
|
||||
op(700, xfx, (#=<)),
|
||||
op(700, xfx, (#=))]).
|
||||
|
||||
:- meta_predicate max(?,0), min(?,0), any(?,0).
|
||||
|
||||
max(X, G) :-
|
||||
|
@@ -1,3 +1,13 @@
|
||||
/**
|
||||
* @file expand_macros.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 15:16:12 2015
|
||||
*
|
||||
* @brief utilities that perform macro expansion for maplist/2 and
|
||||
* friends.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%%
|
||||
|
@@ -1,5 +1,15 @@
|
||||
%%% -*- Mode: Prolog; -*-
|
||||
|
||||
/**
|
||||
* @file flags.yap
|
||||
* @author Theofrastos Mantadelis, Bernd Gutmann, Paulo Moura
|
||||
* @date Tue Nov 17 15:18:02 2015
|
||||
*
|
||||
* @brief Flag Manipulation in Prolog
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
%
|
||||
% Flags was developed at Katholieke Universiteit Leuven
|
||||
@@ -219,6 +229,15 @@
|
||||
flags_print/0,
|
||||
defined_flag/7]).
|
||||
|
||||
/**
|
||||
* @defgroup flags Flag Manipulation in Prolog
|
||||
* @ingroup library
|
||||
*
|
||||
* Routines to manipulate flags: they allow defining, set,
|
||||
* resetting.
|
||||
*/
|
||||
|
||||
|
||||
:- use_module(library(lists), [append/3, memberchk/2, member/2]).
|
||||
|
||||
:- style_check(all).
|
||||
|
@@ -1,8 +1,28 @@
|
||||
/**
|
||||
* @file gensym.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 18:37:13 2015
|
||||
*
|
||||
* @brief Generate a new atom.
|
||||
*
|
||||
*
|
||||
*/
|
||||
:- module(gensym, [
|
||||
gensym/2,
|
||||
reset_gensym/1,
|
||||
reset_gensym/0
|
||||
]).
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup gensym Generate a new symbol.
|
||||
* @ingroup library
|
||||
*
|
||||
* Predicates to create new atoms based on the prefix _Atom_.
|
||||
* They use a counter, stored as a
|
||||
* dynamic predicate, to construct the atom's suffix.
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- dynamic gensym_key/2.
|
||||
|
||||
|
@@ -1,7 +1,12 @@
|
||||
% File : hacks.yap
|
||||
% Author : Vitor Santos Costa
|
||||
% Updated: 2007
|
||||
% Purpose: Prolog hacking
|
||||
/**
|
||||
* @file hacks.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 19:00:25 2015
|
||||
*
|
||||
* @brief Prolog hacking
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(yap_hacks, [
|
||||
current_choicepoint/1,
|
||||
@@ -17,7 +22,17 @@
|
||||
disable_interrupts/0,
|
||||
virtual_alarm/3,
|
||||
context_variables/1
|
||||
]).
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup yap_hacks YAP hacking
|
||||
* @ingroup library
|
||||
*
|
||||
* Manipulate the Prolog stacks, including setting and resetting
|
||||
* choice-points.
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
stack_dump :-
|
||||
stack_dump(-1).
|
||||
|
@@ -1,9 +1,12 @@
|
||||
% This file has been included as an YAP library by Vitor Santos Costa, 1999
|
||||
|
||||
% File : HEAPS.PL
|
||||
% Author : R.A.O'Keefe
|
||||
% Updated: 29 November 1983
|
||||
% Purpose: Implement heaps in Prolog.
|
||||
/**
|
||||
* @file heaps.yap
|
||||
* @author R.A.O'Keefe, included as an YAP library by Vitor Santos Costa, 1999.
|
||||
* @date 29 November 1983
|
||||
*
|
||||
* @brief Implement heaps in Prolog.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(heaps,[
|
||||
add_to_heap/4, % Heap x Key x Datum -> Heap
|
||||
@@ -17,7 +20,7 @@
|
||||
]).
|
||||
|
||||
|
||||
/** @defgroup Heaps Heaps
|
||||
/** @defgroup heaps Heaps
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -33,18 +36,24 @@ there will be, let alone what they are.
|
||||
The following heap manipulation routines are available once included
|
||||
with the `use_module(library(heaps))` command.
|
||||
|
||||
|
||||
*/
|
||||
- add_to_heap/4
|
||||
- empty_heap/1
|
||||
- get_from_heap/4
|
||||
- heap_size/2
|
||||
- heap_to_list/2
|
||||
- list_to_heap/2
|
||||
- min_of_heap/3
|
||||
- min_of_heap/5
|
||||
|
||||
|
||||
/* A heap is a labelled binary tree where the key of each node is less
|
||||
than or equal to the keys of its sons. The point of a heap is that
|
||||
we can keep on adding new elements to the heap and we can keep on
|
||||
taking out the minimum element. If there are N elements total, the
|
||||
total time is O(NlgN). If you know all the elements in advance, you
|
||||
are better off doing a merge-sort, but this file is for when you
|
||||
want to do say a best-first search, and have no idea when you start
|
||||
how many elements there will be, let alone what they are.
|
||||
A heap is a labelled binary tree where the key of each node is less
|
||||
than or equal to the keys of its sons. The point of a heap is that
|
||||
we can keep on adding new elements to the heap and we can keep on
|
||||
taking out the minimum element. If there are N elements total, the
|
||||
total time is O(NlgN). If you know all the elements in advance, you
|
||||
are better off doing a merge-sort, but this file is for when you want
|
||||
to do say a best-first search, and have no idea when you start how
|
||||
many elements there will be, let alone what they are.
|
||||
|
||||
A heap is represented as a triple t(N, Free, Tree) where N is the
|
||||
number of elements in the tree, Free is a list of integers which
|
||||
@@ -70,75 +79,6 @@ with the `use_module(library(heaps))` command.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
|
||||
/**
|
||||
|
||||
|
||||
@pred add_to_heap(+ _Heap_,+ _key_,+ _Datum_,- _NewHeap_)
|
||||
|
||||
|
||||
Inserts the new _Key-Datum_ pair into the heap. The insertion is not
|
||||
stable, that is, if you insert several pairs with the same _Key_ it
|
||||
is not defined which of them will come out first, and it is possible for
|
||||
any of them to come out first depending on the history of the heap.
|
||||
|
||||
*/
|
||||
/** @pred empty_heap(? _Heap_)
|
||||
|
||||
|
||||
Succeeds if _Heap_ is an empty heap.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred get_from_heap(+ _Heap_,- _key_,- _Datum_,- _Heap_)
|
||||
|
||||
|
||||
Returns the _Key-Datum_ pair in _OldHeap_ with the smallest
|
||||
_Key_, and also a _Heap_ which is the _OldHeap_ with that
|
||||
pair deleted.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred heap_size(+ _Heap_, - _Size_)
|
||||
|
||||
|
||||
Reports the number of elements currently in the heap.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred heap_to_list(+ _Heap_, - _List_)
|
||||
|
||||
|
||||
Returns the current set of _Key-Datum_ pairs in the _Heap_ as a
|
||||
_List_, sorted into ascending order of _Keys_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred list_to_heap(+ _List_, - _Heap_)
|
||||
|
||||
|
||||
Takes a list of _Key-Datum_ pairs (such as keysort could be used to sort)
|
||||
and forms them into a heap.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred min_of_heap(+ _Heap_, - _Key1_, - _Datum1_,
|
||||
- _Key2_, - _Datum2_)
|
||||
|
||||
Returns the smallest (Key1) and second smallest (Key2) pairs in the
|
||||
heap, without deleting them.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
/** @pred min_of_heap(+ _Heap_, - _Key_, - _Datum_)
|
||||
|
||||
|
||||
Returns the Key-Datum pair at the top of the heap (which is of course
|
||||
the pair with the smallest Key), but does not remove it from the heap.
|
||||
|
||||
|
||||
*/
|
||||
|
||||
/*
|
||||
@@ -206,7 +146,7 @@ sort2(Key1, Datum1, Key2, Datum2, Key2, Datum2, Key1, Datum1).
|
||||
|
||||
|
||||
|
||||
%% @pred get_from_heap(OldHeap, Key, Datum, NewHeap)
|
||||
%% @pred @pred get_from_heap(+ _Heap_,- _key_,- _Datum_,- _Heap_)
|
||||
%
|
||||
% returns the Key-Datum pair in OldHeap with the smallest Key, and
|
||||
% also a New Heap which is the Old Heap with that pair deleted.
|
||||
@@ -239,7 +179,7 @@ repair_heap(t, t, t, 1) :- !.
|
||||
|
||||
|
||||
|
||||
%% @pred heap_size(Heap, Size)
|
||||
%% @pred heap_size(+ _Heap_, - _Size_)
|
||||
%
|
||||
% reports the number of elements currently in the heap.
|
||||
|
||||
@@ -247,7 +187,7 @@ heap_size(t(Size,_,_), Size).
|
||||
|
||||
|
||||
|
||||
%% @pred heap_to_list(Heap, List)
|
||||
%% @pred heap_to_list(+ _Heap_, - _List_)
|
||||
%
|
||||
% returns the current set of Key-Datum pairs in the Heap as a
|
||||
% List, sorted into ascending order of Keys. This is included
|
||||
@@ -280,7 +220,7 @@ heap_tree_to_list(T, [], T).
|
||||
|
||||
|
||||
|
||||
%% @pred list_to_heap(List, Heap)
|
||||
%% @pred list_to_heap(+ _List_, - _Heap_)
|
||||
%
|
||||
% takes a list of Key-Datum pairs (such as keysort could be used to
|
||||
% sort) and forms them into a heap. We could do that a wee bit
|
||||
@@ -307,15 +247,22 @@ list_to_heap([Key-Datum|Rest], M, OldTree, Heap) :-
|
||||
% course the pair with the smallest Key), but does not remove it
|
||||
% from the heap. It fails if the heap is empty.
|
||||
|
||||
%% @pred min_of_heap(Heap, Key1, Datum1, Key2, Datum2)
|
||||
|
||||
/** @pred min_of_heap(+ _Heap_, - _Key_, - _Datum_)
|
||||
|
||||
|
||||
Returns the Key-Datum pair at the top of the heap (which is of course
|
||||
the pair with the smallest Key), but does not remove it from the heap.
|
||||
*/
|
||||
min_of_heap(t(_,_,t(Key,Datum,_,_)), Key, Datum).
|
||||
|
||||
|
||||
%% @pred @pred min_of_heap(+ _Heap_, - _Key1_, - _Datum1_,
|
||||
- _Key2_, - _Datum2_)
|
||||
%
|
||||
% returns the smallest (Key1) and second smallest (Key2) pairs in
|
||||
% the heap, without deleting them. It fails if the heap does not
|
||||
% have at least two elements.
|
||||
|
||||
min_of_heap(t(_,_,t(Key,Datum,_,_)), Key, Datum).
|
||||
|
||||
|
||||
min_of_heap(t(_,_,t(Key1,Datum1,Lson,Rson)), Key1, Datum1, Key2, Datum2) :-
|
||||
min_of_heap(Lson, Rson, Key2, Datum2).
|
||||
|
||||
@@ -325,6 +272,11 @@ min_of_heap(t(Ka,_Da,_,_), t(Kb,Db,_,_), Kb, Db) :-
|
||||
min_of_heap(t(Ka,Da,_,_), _, Ka, Da).
|
||||
min_of_heap(t, t(Kb,Db,_,_), Kb, Db).
|
||||
|
||||
/** @pred empty_heap(? _Heap_)
|
||||
|
||||
|
||||
Succeeds if _Heap_ is an empty heap.
|
||||
*/
|
||||
empty_heap(t(0,[],t)).
|
||||
|
||||
|
||||
|
@@ -1,3 +1,13 @@
|
||||
/**
|
||||
* @file itries.yap
|
||||
* @author Ricardo Rocha
|
||||
* @date
|
||||
*
|
||||
* @brief Tries module for ILP
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
/*********************************
|
||||
File: itries.yap
|
||||
Author: Ricardo Rocha
|
||||
|
@@ -3,8 +3,35 @@
|
||||
% $Id: lam_mpi.yap,v 1.1 2006-06-04 18:43:38 nunofonseca Exp $
|
||||
|
||||
|
||||
/** @defgroup LAM LAM
|
||||
@ingroup library
|
||||
:- module(lam_mpi, [
|
||||
mpi_init/0,
|
||||
mpi_finalize/0,
|
||||
mpi_comm_size/1,
|
||||
mpi_comm_rank/1,
|
||||
mpi_version/2,
|
||||
mpi_send/3,
|
||||
mpi_isend/4,
|
||||
mpi_recv/3,
|
||||
mpi_irecv/3,
|
||||
mpi_wait/2,
|
||||
mpi_wait_recv/3,
|
||||
mpi_test/2,
|
||||
mpi_test_recv/3,
|
||||
mpi_bcast/2,
|
||||
mpi_ibcast2/2,
|
||||
mpi_ibcast2/3,
|
||||
mpi_bcast2/2,
|
||||
mpi_bcast2/3,
|
||||
mpi_barrier/0,
|
||||
mpi_msg_buffer_size/2,
|
||||
mpi_msg_size/2,
|
||||
mpi_gc/0,
|
||||
mpi_default_buffer_size/2
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup lam_mpi MPI Interface
|
||||
* @ingroup library
|
||||
@{
|
||||
|
||||
This library provides a set of utilities for interfacing with LAM MPI.
|
||||
@@ -25,8 +52,6 @@ synchronization among all processes. Note that a collective
|
||||
communication means that all processes call the same predicate. To be
|
||||
able to use a regular `mpi_recv` to receive the messages, one
|
||||
should use `mpi_bcast2`.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred mpi_bcast2(+ _Root_, ? _Data_)
|
||||
|
||||
@@ -186,31 +211,6 @@ message and _Data_ with the message itself.
|
||||
|
||||
|
||||
*/
|
||||
:- module(lam_mpi, [
|
||||
mpi_init/0,
|
||||
mpi_finalize/0,
|
||||
mpi_comm_size/1,
|
||||
mpi_comm_rank/1,
|
||||
mpi_version/2,
|
||||
mpi_send/3,
|
||||
mpi_isend/4,
|
||||
mpi_recv/3,
|
||||
mpi_irecv/3,
|
||||
mpi_wait/2,
|
||||
mpi_wait_recv/3,
|
||||
mpi_test/2,
|
||||
mpi_test_recv/3,
|
||||
mpi_bcast/2,
|
||||
mpi_ibcast2/2,
|
||||
mpi_ibcast2/3,
|
||||
mpi_bcast2/2,
|
||||
mpi_bcast2/3,
|
||||
mpi_barrier/0,
|
||||
mpi_msg_buffer_size/2,
|
||||
mpi_msg_size/2,
|
||||
mpi_gc/0,
|
||||
mpi_default_buffer_size/2
|
||||
]).
|
||||
|
||||
:- load_foreign_files([yap_mpi], [], init_mpi).
|
||||
|
||||
|
@@ -1,5 +1,14 @@
|
||||
/**
|
||||
* @file heaps.yap
|
||||
* @author Ulrich Neumerkel
|
||||
* @date 2009
|
||||
*
|
||||
* @brief Lambda expressions in Prolog.
|
||||
*
|
||||
*
|
||||
*/
|
||||
/*
|
||||
Author: Ulrich Neumerkel
|
||||
Author:
|
||||
E-mail: ulrich@complang.tuwien.ac.at
|
||||
Copyright (C): 2009 Ulrich Neumerkel. All rights reserved.
|
||||
|
||||
@@ -40,7 +49,8 @@ official policies, either expressed or implied, of Ulrich Neumerkel.
|
||||
(+\)/2, (+\)/3, (+\)/4, (+\)/5, (+\)/6, (+\)/7,
|
||||
op(201,xfx,+\)]).
|
||||
|
||||
/** <module> Lambda expressions
|
||||
/**
|
||||
@defgroup Lambda expressions
|
||||
@ingroup library
|
||||
|
||||
This library provides lambda expressions to simplify higher order
|
||||
|
@@ -1,3 +1,12 @@
|
||||
/**
|
||||
* @file lineutils.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 22:02:22 2015
|
||||
*
|
||||
* @brief line text processing.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(line_utils,
|
||||
[search_for/2,
|
||||
@@ -21,7 +30,7 @@
|
||||
process/2
|
||||
]).
|
||||
|
||||
/** @defgroup LineUtilities Line Manipulation Utilities
|
||||
/** @defgroup line_utils Line Manipulation Utilities
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -32,6 +41,7 @@ available by loading the
|
||||
:- use_module(library(lineutils)).
|
||||
~~~~
|
||||
|
||||
|
||||
*/
|
||||
|
||||
:- meta_predicate
|
||||
|
@@ -15,13 +15,15 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/*
|
||||
|
||||
emulates listing.pl, but just the interface for now.
|
||||
|
||||
/**
|
||||
* @file listing.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 22:03:59 2015
|
||||
*
|
||||
* @brief Emulate SWI Prolog's listing.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(swi_listing,
|
||||
[ listing/0,
|
||||
listing/1,
|
||||
@@ -31,6 +33,17 @@
|
||||
]).
|
||||
|
||||
|
||||
|
||||
/*
|
||||
|
||||
* @defgroup swi_listing SWI Prolog listing emulation
|
||||
* @ingroup library
|
||||
|
||||
emulates listing.pl, but just the interface for now.
|
||||
|
||||
*/
|
||||
|
||||
|
||||
:- meta_predicate portray_clause( +, + , : ).
|
||||
|
||||
portray_clause(Stream, Term, M:Options) :-
|
||||
|
@@ -1,10 +1,58 @@
|
||||
/**
|
||||
* @file lists.yap
|
||||
* @author Bob Welham, Lawrence Byrd, and R. A. O'Keefe. Contributions from Vitor Santos Costa, Jan Wielemaker and others.
|
||||
* @date 1999
|
||||
*
|
||||
* @brief List Manipulation Predicates
|
||||
*
|
||||
*
|
||||
*/
|
||||
% This file has been included as an YAP library by Vitor Santos Costa, 1999
|
||||
|
||||
%
|
||||
% This file includes code from Bob Welham, Lawrence Byrd, and R. A. O'Keefe.
|
||||
%
|
||||
:- module(lists,
|
||||
[
|
||||
append/3,
|
||||
append/2,
|
||||
delete/3,
|
||||
intersection/3,
|
||||
flatten/2,
|
||||
last/2,
|
||||
list_concat/2,
|
||||
max_list/2,
|
||||
list_to_set/2,
|
||||
member/2,
|
||||
memberchk/2,
|
||||
min_list/2,
|
||||
nextto/3,
|
||||
nth/3,
|
||||
nth/4,
|
||||
nth0/3,
|
||||
nth0/4,
|
||||
nth1/3,
|
||||
nth1/4,
|
||||
numlist/3,
|
||||
permutation/2,
|
||||
prefix/2,
|
||||
remove_duplicates/2,
|
||||
reverse/2,
|
||||
same_length/2,
|
||||
select/3,
|
||||
selectchk/3,
|
||||
sublist/2,
|
||||
substitute/4,
|
||||
subtract/3,
|
||||
suffix/2,
|
||||
sum_list/2,
|
||||
sum_list/3,
|
||||
sumlist/2
|
||||
]).
|
||||
|
||||
/** @defgroup Lists List Manipulation
|
||||
|
||||
:- use_module(library(error),
|
||||
[must_be/2]).
|
||||
|
||||
|
||||
/** @defgroup lists List Manipulation
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -12,56 +60,7 @@ The following list manipulation routines are available once included
|
||||
with the `use_module(library(lists))` command.
|
||||
|
||||
*/
|
||||
/**
|
||||
@pred append(? _Prefix_,? _Suffix_,? _Combined_)
|
||||
|
||||
|
||||
True when all three arguments are lists, and the members of
|
||||
_Combined_ are the members of _Prefix_ followed by the members of _Suffix_.
|
||||
It may be used to form _Combined_ from a given _Prefix_, _Suffix_ or to take
|
||||
a given _Combined_ apart.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred append(? _Lists_,? _Combined_)
|
||||
|
||||
Holds if the lists of _Lists_ can be concatenated as a
|
||||
_Combined_ list.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred flatten(+ _List_, ? _FlattenedList_)
|
||||
|
||||
|
||||
Flatten a list of lists _List_ into a single list
|
||||
_FlattenedList_.
|
||||
|
||||
~~~~~{.prolog}
|
||||
?- flatten([[1],[2,3],[4,[5,6],7,8]],L).
|
||||
|
||||
L = [1,2,3,4,5,6,7,8] ? ;
|
||||
|
||||
no
|
||||
~~~~~
|
||||
|
||||
|
||||
*/
|
||||
/** @pred intersection(+ _Set1_, + _Set2_, + _Set3_)
|
||||
|
||||
|
||||
Succeeds if _Set3_ unifies with the intersection of _Set1_ and
|
||||
_Set2_. _Set1_ and _Set2_ are lists without duplicates. They
|
||||
need not be ordered.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred last(+ _List_,? _Last_)
|
||||
|
||||
|
||||
True when _List_ is a list and _Last_ is identical to its last element.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred list_concat(+ _Lists_,? _List_)
|
||||
|
||||
|
||||
@@ -186,121 +185,10 @@ Modes `same_length(-,+)` and `same_length(+,-)` generate either list given
|
||||
the other; mode `same_length(-,-)` generates two lists of the same length,
|
||||
in which case the arguments will be bound to lists of length 0, 1, 2, ...
|
||||
|
||||
|
||||
*/
|
||||
/** @pred select(? _Element_, ? _List_, ? _Residue_)
|
||||
|
||||
|
||||
True when _Set_ is a list, _Element_ occurs in _List_, and
|
||||
_Residue_ is everything in _List_ except _Element_ (things
|
||||
stay in the same order).
|
||||
|
||||
|
||||
*/
|
||||
/** @pred selectchk(? _Element_, ? _List_, ? _Residue_)
|
||||
|
||||
|
||||
Semi-deterministic selection from a list. Steadfast: defines as
|
||||
|
||||
~~~~~{.prolog}
|
||||
selectchk(Elem, List, Residue) :-
|
||||
select(Elem, List, Rest0), !,
|
||||
Rest = Rest0.
|
||||
~~~~~
|
||||
|
||||
|
||||
*/
|
||||
/** @pred sublist(? _Sublist_, ? _List_)
|
||||
|
||||
|
||||
True when both `append(_,Sublist,S)` and `append(S,_,List)` hold.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred subtract(+ _Set_, + _Delete_, ? _Result_)
|
||||
|
||||
|
||||
Delete all elements from _Set_ that occur in _Delete_ (a set)
|
||||
and unify the result with _Result_. Deletion is based on
|
||||
unification using memberchk/2. The complexity is
|
||||
`|Delete|\*|Set|`.
|
||||
|
||||
See ord_subtract/3.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
/** @pred suffix(? _Suffix_, ? _List_)
|
||||
|
||||
|
||||
Holds when `append(_,Suffix,List)` holds.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred sum_list(? _Numbers_, + _SoFar_, ? _Total_)
|
||||
|
||||
True when _Numbers_ is a list of numbers, and _Total_ is the sum of their total plus _SoFar_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred sum_list(? _Numbers_, ? _Total_)
|
||||
|
||||
|
||||
True when _Numbers_ is a list of numbers, and _Total_ is their sum.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred sumlist(? _Numbers_, ? _Total_)
|
||||
|
||||
|
||||
True when _Numbers_ is a list of integers, and _Total_ is their
|
||||
sum. The same as sum_list/2, please do use sum_list/2
|
||||
instead.
|
||||
|
||||
|
||||
*/
|
||||
:- module(lists,
|
||||
[
|
||||
append/3,
|
||||
append/2,
|
||||
delete/3,
|
||||
intersection/3,
|
||||
flatten/2,
|
||||
last/2,
|
||||
list_concat/2,
|
||||
max_list/2,
|
||||
list_to_set/2,
|
||||
member/2,
|
||||
memberchk/2,
|
||||
min_list/2,
|
||||
nextto/3,
|
||||
nth/3,
|
||||
nth/4,
|
||||
nth0/3,
|
||||
nth0/4,
|
||||
nth1/3,
|
||||
nth1/4,
|
||||
numlist/3,
|
||||
permutation/2,
|
||||
prefix/2,
|
||||
remove_duplicates/2,
|
||||
reverse/2,
|
||||
same_length/2,
|
||||
select/3,
|
||||
selectchk/3,
|
||||
sublist/2,
|
||||
substitute/4,
|
||||
subtract/3,
|
||||
suffix/2,
|
||||
sum_list/2,
|
||||
sum_list/3,
|
||||
sumlist/2
|
||||
]).
|
||||
:- use_module(library(error),
|
||||
[must_be/2]).
|
||||
|
||||
|
||||
%% append(+ListOfLists, ?List)
|
||||
%% @pred append(? _Lists_,? _Combined_)
|
||||
%
|
||||
% Concatenate a list of lists. Is true if Lists is a list of
|
||||
% lists, and List is the concatenation of these lists.
|
||||
@@ -319,10 +207,11 @@ append_([L1,L2|[L3|LL]], L) :-
|
||||
append(L1,L2,LI),
|
||||
append_([LI|[L3|LL]],L).
|
||||
|
||||
/** @pred last(+ _List_,? _Last_)
|
||||
|
||||
% last(List, Last)
|
||||
% is true when List is a List and Last is identical to its last element.
|
||||
% This could be defined as last(L, X) :- append(_, [X], L).
|
||||
|
||||
True when _List_ is a list and _Last_ is identical to its last element.
|
||||
d(_, [X], L).
|
||||
|
||||
last([H|List], Last) :-
|
||||
last(List, H, Last).
|
||||
@@ -494,34 +383,43 @@ same_length([], []).
|
||||
same_length([_|List1], [_|List2]) :-
|
||||
same_length(List1, List2).
|
||||
|
||||
%% selectchk(+Elem, +List, -Rest) is semidet.
|
||||
%
|
||||
% Semi-deterministic removal of first element in List that unifies
|
||||
% Elem.
|
||||
|
||||
/** @pred selectchk(? _Element_, ? _List_, ? _Residue_)
|
||||
|
||||
|
||||
Semi-deterministic selection from a list. Steadfast: defines as
|
||||
|
||||
~~~~~{.prolog}
|
||||
selectchk(Elem, List, Residue) :-
|
||||
select(Elem, List, Rest0), !,
|
||||
Rest = Rest0.
|
||||
~~~~~
|
||||
*/
|
||||
selectchk(Elem, List, Rest) :-
|
||||
select(Elem, List, Rest0), !,
|
||||
Rest = Rest0.
|
||||
|
||||
|
||||
% select(?Element, ?Set, ?Residue)
|
||||
% is true when Set is a list, Element occurs in Set, and Residue is
|
||||
% everything in Set except Element (things stay in the same order).
|
||||
|
||||
/** @pred select(? _Element_, ? _List_, ? _Residue_)
|
||||
|
||||
|
||||
True when _Set_ is a list, _Element_ occurs in _List_, and
|
||||
_Residue_ is everything in _List_ except _Element_ (things
|
||||
stay in the same order).
|
||||
*/
|
||||
select(Element, [Element|Rest], Rest).
|
||||
select(Element, [Head|Tail], [Head|Rest]) :-
|
||||
select(Element, Tail, Rest).
|
||||
|
||||
|
||||
% sublist(Sublist, List)
|
||||
% is true when both append(_,Sublist,S) and append(S,_,List) hold.
|
||||
|
||||
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
%% sublist(?Sub, +List) is nondet.
|
||||
%
|
||||
% True if all elements of Sub appear in List in the same order.
|
||||
|
||||
%
|
||||
% ALlo, both `append(_,Sublist,S)` and `append(S,_,List)` hold.
|
||||
sublist(L, L).
|
||||
sublist(Sub, [H|T]) :-
|
||||
'$sublist1'(T, H, Sub).
|
||||
@@ -545,21 +443,38 @@ substitute2([X0|XList], X, Y, [Y|YList]) :-
|
||||
substitute2([X0|XList], X, Y, [X0|YList]) :-
|
||||
substitute2(XList, X, Y, YList).
|
||||
|
||||
% suffix(Suffix, List)
|
||||
% holds when append(_,Suffix,List) holds.
|
||||
/** @pred suffix(? _Suffix_, ? _List_)
|
||||
|
||||
Holds when `append(_,Suffix,List)` holds.
|
||||
*/
|
||||
suffix(Suffix, Suffix).
|
||||
suffix(Suffix, [_|List]) :-
|
||||
suffix(Suffix,List).
|
||||
|
||||
% sumlist(Numbers, Total)
|
||||
% is true when Numbers is a list of integers, and Total is their sum.
|
||||
/** @pred sumlist(? _Numbers_, ? _Total_)
|
||||
|
||||
|
||||
True when _Numbers_ is a list of integers, and _Total_ is their
|
||||
sum. The same as sum_list/2, please do use sum_list/2
|
||||
instead.
|
||||
|
||||
|
||||
*/
|
||||
sumlist(Numbers, Total) :-
|
||||
sumlist(Numbers, 0, Total).
|
||||
|
||||
/** @pred sum_list(? _Numbers_, + _SoFar_, ? _Total_)
|
||||
|
||||
True when _Numbers_ is a list of numbers, and _Total_ is the sum of their total plus _SoFar_.
|
||||
*/
|
||||
sum_list(Numbers, SoFar, Total) :-
|
||||
sumlist(Numbers, SoFar, Total).
|
||||
|
||||
/** @pred sum_list(? _Numbers_, ? _Total_)
|
||||
|
||||
|
||||
True when _Numbers_ is a list of numbers, and _Total_ is their sum.
|
||||
*/
|
||||
sum_list(Numbers, Total) :-
|
||||
sumlist(Numbers, 0, Total).
|
||||
|
||||
@@ -584,9 +499,20 @@ list_concat([H|T], [H|Lf], Li) :-
|
||||
|
||||
|
||||
|
||||
%
|
||||
% flatten a list
|
||||
%
|
||||
/** @pred flatten(+ _List_, ? _FlattenedList_)
|
||||
|
||||
|
||||
Flatten a list of lists _List_ into a single list
|
||||
_FlattenedList_.
|
||||
|
||||
~~~~~{.prolog}
|
||||
?- flatten([[1],[2,3],[4,[5,6],7,8]],L).
|
||||
|
||||
L = [1,2,3,4,5,6,7,8] ? ;
|
||||
|
||||
no
|
||||
~~~~~
|
||||
*/
|
||||
flatten(X,Y) :- flatten_list(X,Y,[]).
|
||||
|
||||
flatten_list(V) --> {var(V)}, !, [V].
|
||||
@@ -639,6 +565,17 @@ numlist_(L, U, [L|Ns]) :-
|
||||
numlist_(L2, U, Ns).
|
||||
|
||||
|
||||
/** @pred intersection(+ _Set1_, + _Set2_, + _Set3_)
|
||||
|
||||
|
||||
Succeeds if _Set3_ unifies with the intersection of _Set1_ and
|
||||
_Set2_. _Set1_ and _Set2_ are lists without duplicates. They
|
||||
need not be ordered.
|
||||
|
||||
The code was copied from SWI-Prolog's list library.
|
||||
|
||||
*/
|
||||
|
||||
% copied from SWI lists library.
|
||||
intersection([], _, []) :- !.
|
||||
intersection([X|T], L, Intersect) :-
|
||||
|
@@ -1,15 +1,13 @@
|
||||
% Also has code from:
|
||||
% File : APPLIC.PL
|
||||
% Author : Lawrence Byrd + Richard A. O'Keefe
|
||||
% Updated: 4 August 1984 and Ken Johnson 11-8-87
|
||||
% Purpose: Various "function" application routines based on apply/2.
|
||||
% Needs : append/3 from listut.pl
|
||||
|
||||
|
||||
% File : apply_macros.yap
|
||||
% Author : E. Alphonse from code by Joachim Schimpf, Jan Wielemaker, Vitor Santos Costa
|
||||
% Purpose: Macros to apply a predicate to all elements
|
||||
% of a list or to all sub-terms of a term.
|
||||
/**
|
||||
* @file mapargs.yap
|
||||
* @author Lawrence Byrd + Richard A. O'Keefe, VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @author : E. Alphonse from code by Joachim Schimpf, Jan Wielemaker, Vitor Santos Costa
|
||||
* @date 4 August 1984 and Ken Johnson 11-8-87
|
||||
*
|
||||
* @brief Macros to apply a predicate to all sub-terms of a term.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(mapargs,[ mapargs/2, % :Goal, +S
|
||||
@@ -22,7 +20,13 @@
|
||||
foldargs/5, % :Pred, +S, ?S1, ?V0, ?V
|
||||
foldargs/6, % :Pred, +S, ?S1, ?S2, ?V0, ?V
|
||||
foldargs/7 % :Pred, +S, ?S1, ?S2, ?S3, ?V0, ?V
|
||||
]).
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup mapargs Apply a predicate to all arguments of a term
|
||||
* @ingroup library
|
||||
*/
|
||||
|
||||
|
||||
:- use_module(library(maputils)).
|
||||
:- use_module(library(lists), [append/3]).
|
||||
|
@@ -1,27 +1,48 @@
|
||||
/**
|
||||
|
||||
@defgroup YAPMapList Meta- and Control Predicates
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
* @file maplist.yap
|
||||
* @author Lawrence Byrd + Richard A. O'Keefe, VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @author : E. Alphonse from code by Joachim Schimpf, Jan Wielemaker, Vitor Santos Costa
|
||||
* @date 4 August 1984 and Ken Johnson 11-8-87
|
||||
*
|
||||
* @brief Macros to apply a predicate to all elements of a list.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
% Also has code from:
|
||||
% File : APPLIC.PL
|
||||
% Author : Lawrence Byrd + Richard A. O'Keefe
|
||||
% Updated: 4 August 1984 and Ken Johnson 11-8-87
|
||||
% Purpose: Various "function" application routines based on apply/2.
|
||||
% Needs : append/3 from listut.pl
|
||||
|
||||
|
||||
% File : apply_macros.yap
|
||||
% Author : E. Alphonse from code by Joachim Schimpf, Jan Wielemaker, Vitor Santos Costa
|
||||
% Purpose: Macros to apply a predicate to all elements
|
||||
% of a list or to all sub-terms of a term.
|
||||
:- module(maplist,
|
||||
[maplist/2,
|
||||
maplist/3,
|
||||
maplist/4,
|
||||
maplist/5,
|
||||
checklist/2,
|
||||
checknodes/2,
|
||||
convlist/3,
|
||||
foldl/4,
|
||||
foldl/5,
|
||||
foldl/6,
|
||||
foldl/7,
|
||||
foldl2/6,
|
||||
foldl2/7,
|
||||
foldl2/8,
|
||||
foldl3/8,
|
||||
foldl4/10,
|
||||
include/3,
|
||||
exclude/3,
|
||||
mapnodes/3,
|
||||
partition/4,
|
||||
partition/5,
|
||||
scanl/4,
|
||||
scanl/5,
|
||||
scanl/6,
|
||||
scanl/7,
|
||||
selectlist/3,
|
||||
selectlist/4,
|
||||
selectlists/5,
|
||||
sumlist/4,
|
||||
sumnodes/4
|
||||
]).
|
||||
|
||||
/**
|
||||
* @file maplist.yap
|
||||
*
|
||||
* @defgroup maplist Map List and Term Operations
|
||||
* @ingroup library
|
||||
*
|
||||
@@ -79,39 +100,6 @@ trans(X,X).
|
||||
|
||||
*/
|
||||
|
||||
:- module(maplist,
|
||||
[maplist/2,
|
||||
maplist/3,
|
||||
maplist/4,
|
||||
maplist/5,
|
||||
checklist/2,
|
||||
checknodes/2,
|
||||
convlist/3,
|
||||
foldl/4,
|
||||
foldl/5,
|
||||
foldl/6,
|
||||
foldl/7,
|
||||
foldl2/6,
|
||||
foldl2/7,
|
||||
foldl2/8,
|
||||
foldl3/8,
|
||||
foldl4/10,
|
||||
include/3,
|
||||
exclude/3,
|
||||
mapnodes/3,
|
||||
partition/4,
|
||||
partition/5,
|
||||
scanl/4,
|
||||
scanl/5,
|
||||
scanl/6,
|
||||
scanl/7,
|
||||
selectlist/3,
|
||||
selectlist/4,
|
||||
selectlists/5,
|
||||
sumlist/4,
|
||||
sumnodes/4
|
||||
]).
|
||||
|
||||
|
||||
|
||||
/** @pred maplist(+ _Pred_,+ _List1_,+ _List2_)
|
||||
|
@@ -1,16 +1,16 @@
|
||||
/**
|
||||
* @file maputils.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 22:48:58 2015
|
||||
*
|
||||
* @brief Auxiliary routines for map... libraries
|
||||
*
|
||||
*
|
||||
*/
|
||||
%%%%%%%%%%%%%%%%%%%%
|
||||
% map utilities
|
||||
%%%%%%%%%%%%%%%%%%%%
|
||||
|
||||
/**
|
||||
* @file maputils.yap
|
||||
*
|
||||
* @addtogroup maplist
|
||||
*
|
||||
* Auxiliary routines
|
||||
*
|
||||
*@{
|
||||
*/
|
||||
:- module(maputils,
|
||||
[compile_aux/2,
|
||||
goal_expansion_allowed/0,
|
||||
@@ -18,6 +18,13 @@
|
||||
aux_preds/5,
|
||||
append_args/3]).
|
||||
|
||||
/**
|
||||
* @addtogroup maplist
|
||||
*
|
||||
* Auxiliary routines
|
||||
*
|
||||
*@{
|
||||
*/
|
||||
:- use_module(library(lists), [append/3]).
|
||||
|
||||
:- dynamic number_of_expansions/1.
|
||||
|
@@ -1,5 +1,39 @@
|
||||
/**
|
||||
* @file matlab.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 22:51:48 2015
|
||||
*
|
||||
* @brief YAP Matlab interface.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
/** @defgroup MATLAB MATLAB Package Interface
|
||||
|
||||
:- module(matlab,
|
||||
[start_matlab/1,
|
||||
close_matlab/0,
|
||||
matlab_on/0,
|
||||
matlab_eval_string/1,
|
||||
matlab_eval_string/2,
|
||||
matlab_cells/2,
|
||||
matlab_cells/3,
|
||||
matlab_initialized_cells/4,
|
||||
matlab_zeros/2,
|
||||
matlab_zeros/3,
|
||||
matlab_zeros/4,
|
||||
matlab_matrix/4,
|
||||
matlab_vector/2,
|
||||
matlab_vector/3,
|
||||
matlab_set/4,
|
||||
matlab_get_variable/2,
|
||||
matlab_item/3,
|
||||
matlab_item/4,
|
||||
matlab_item1/3,
|
||||
matlab_item1/4,
|
||||
matlab_sequence/3,
|
||||
matlab_call/2]).
|
||||
|
||||
/** @defgroup matlab MATLAB Package Interface
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -20,7 +54,9 @@ export LD_LIBRARY_PATH=''$MATLAB_HOME"/sys/os/glnxa64:''$MATLAB_HOME"/bin/glnxa6
|
||||
where `MATLAB_HOME` is the directory where matlab is installed
|
||||
at. Please replace `ax64` for `x86` on a 32-bit PC.
|
||||
|
||||
*/
|
||||
|
||||
/*
|
||||
|
||||
@pred start_matlab(+ _Options_)
|
||||
|
||||
@@ -190,29 +226,6 @@ variable with name _Array_. Corresponds to the MATLAB command
|
||||
|
||||
|
||||
*/
|
||||
:- module(matlab,
|
||||
[start_matlab/1,
|
||||
close_matlab/0,
|
||||
matlab_on/0,
|
||||
matlab_eval_string/1,
|
||||
matlab_eval_string/2,
|
||||
matlab_cells/2,
|
||||
matlab_cells/3,
|
||||
matlab_initialized_cells/4,
|
||||
matlab_zeros/2,
|
||||
matlab_zeros/3,
|
||||
matlab_zeros/4,
|
||||
matlab_matrix/4,
|
||||
matlab_vector/2,
|
||||
matlab_vector/3,
|
||||
matlab_set/4,
|
||||
matlab_get_variable/2,
|
||||
matlab_item/3,
|
||||
matlab_item/4,
|
||||
matlab_item1/3,
|
||||
matlab_item1/4,
|
||||
matlab_sequence/3,
|
||||
matlab_call/2]).
|
||||
|
||||
:- ensure_loaded(library(lists)).
|
||||
|
||||
|
@@ -14,6 +14,79 @@
|
||||
* comments: Have some fun with blobs *
|
||||
* *
|
||||
*************************************************************************/
|
||||
/**
|
||||
* @file matrix.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 22:53:40 2015
|
||||
*
|
||||
* @brief Vector, Array and Matrix library
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module( matrix,
|
||||
[(<==)/2, op(800, xfx, '<=='),
|
||||
op(700, xfx, in),
|
||||
op(700, xfx, ins),
|
||||
op(450, xfx, ..), % should bind more tightly than \/
|
||||
op(710, xfx, of), of/2,
|
||||
matrix_new/3,
|
||||
matrix_new/4,
|
||||
matrix_new_set/4,
|
||||
matrix_dims/2,
|
||||
matrix_ndims/2,
|
||||
matrix_size/2,
|
||||
matrix_type/2,
|
||||
matrix_to_list/2,
|
||||
matrix_to_lists/2,
|
||||
matrix_get/3,
|
||||
matrix_set/3,
|
||||
matrix_set_all/2,
|
||||
matrix_add/3,
|
||||
matrix_inc/2,
|
||||
matrix_dec/2,
|
||||
matrix_mult/2,
|
||||
matrix_inc/3,
|
||||
matrix_dec/3,
|
||||
matrix_arg_to_offset/3,
|
||||
matrix_offset_to_arg/3,
|
||||
matrix_max/2,
|
||||
matrix_maxarg/2,
|
||||
matrix_min/2,
|
||||
matrix_minarg/2,
|
||||
matrix_sum/2,
|
||||
matrix_sum_out/3,
|
||||
matrix_sum_out_several/3,
|
||||
matrix_sum_logs_out/3,
|
||||
matrix_sum_logs_out_several/3,
|
||||
matrix_add_to_all/2,
|
||||
matrix_agg_lines/3,
|
||||
matrix_agg_cols/3,
|
||||
matrix_to_logs/1,
|
||||
matrix_to_exps/1,
|
||||
matrix_to_exps2/1,
|
||||
matrix_to_logs/2,
|
||||
matrix_to_exps/2,
|
||||
matrix_op/4,
|
||||
matrix_op_to_all/4,
|
||||
matrix_op_to_lines/4,
|
||||
matrix_op_to_cols/4,
|
||||
matrix_shuffle/3,
|
||||
matrix_transpose/2,
|
||||
matrix_set_all_that_disagree/5,
|
||||
matrix_expand/3,
|
||||
matrix_select/4,
|
||||
matrix_column/3,
|
||||
matrix_get/2,
|
||||
matrix_set/2,
|
||||
foreach/2,
|
||||
foreach/4,
|
||||
op(50, yf, []),
|
||||
op(50, yf, '()'),
|
||||
op(100, xfy, '.'),
|
||||
op(100, fy, '.')
|
||||
]).
|
||||
|
||||
/** @defgroup matrix Matrix Library
|
||||
@ingroup library
|
||||
@@ -569,68 +642,6 @@ Unify _NElems_ with the type of the elements in _Matrix_.
|
||||
|
||||
|
||||
*/
|
||||
:- module( matrix,
|
||||
[(<==)/2, op(800, xfx, '<=='),
|
||||
op(700, xfx, in),
|
||||
op(700, xfx, ins),
|
||||
op(450, xfx, ..), % should bind more tightly than \/
|
||||
op(710, xfx, of), of/2,
|
||||
matrix_new/3,
|
||||
matrix_new/4,
|
||||
matrix_new_set/4,
|
||||
matrix_dims/2,
|
||||
matrix_ndims/2,
|
||||
matrix_size/2,
|
||||
matrix_type/2,
|
||||
matrix_to_list/2,
|
||||
matrix_to_lists/2,
|
||||
matrix_get/3,
|
||||
matrix_set/3,
|
||||
matrix_set_all/2,
|
||||
matrix_add/3,
|
||||
matrix_inc/2,
|
||||
matrix_dec/2,
|
||||
matrix_mult/2,
|
||||
matrix_inc/3,
|
||||
matrix_dec/3,
|
||||
matrix_arg_to_offset/3,
|
||||
matrix_offset_to_arg/3,
|
||||
matrix_max/2,
|
||||
matrix_maxarg/2,
|
||||
matrix_min/2,
|
||||
matrix_minarg/2,
|
||||
matrix_sum/2,
|
||||
matrix_sum_out/3,
|
||||
matrix_sum_out_several/3,
|
||||
matrix_sum_logs_out/3,
|
||||
matrix_sum_logs_out_several/3,
|
||||
matrix_add_to_all/2,
|
||||
matrix_agg_lines/3,
|
||||
matrix_agg_cols/3,
|
||||
matrix_to_logs/1,
|
||||
matrix_to_exps/1,
|
||||
matrix_to_exps2/1,
|
||||
matrix_to_logs/2,
|
||||
matrix_to_exps/2,
|
||||
matrix_op/4,
|
||||
matrix_op_to_all/4,
|
||||
matrix_op_to_lines/4,
|
||||
matrix_op_to_cols/4,
|
||||
matrix_shuffle/3,
|
||||
matrix_transpose/2,
|
||||
matrix_set_all_that_disagree/5,
|
||||
matrix_expand/3,
|
||||
matrix_select/4,
|
||||
matrix_column/3,
|
||||
matrix_get/2,
|
||||
matrix_set/2,
|
||||
foreach/2,
|
||||
foreach/4,
|
||||
op(50, yf, []),
|
||||
op(50, yf, '()'),
|
||||
op(100, xfy, '.'),
|
||||
op(100, fy, '.')
|
||||
]).
|
||||
|
||||
:- load_foreign_files([matrix], [], init_matrix).
|
||||
|
||||
|
@@ -15,7 +15,47 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/** @defgroup NonhYBacktrackable_Data_Structures Non-Backtrackable Data Structures
|
||||
/**
|
||||
* @file nb.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 23:18:13 2015
|
||||
*
|
||||
* @brief stub for global (non-backtrackable) variables.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(nb, [
|
||||
nb_create_accumulator/2,
|
||||
nb_add_to_accumulator/2,
|
||||
nb_accumulator_value/2,
|
||||
nb_queue/1,
|
||||
nb_queue/2,
|
||||
nb_queue_close/3,
|
||||
nb_queue_enqueue/2,
|
||||
nb_queue_dequeue/2,
|
||||
nb_queue_peek/2,
|
||||
nb_queue_empty/1,
|
||||
nb_queue_size/2,
|
||||
nb_queue_replace/3,
|
||||
nb_heap/2,
|
||||
nb_heap_close/1,
|
||||
nb_heap_add/3,
|
||||
nb_heap_del/3,
|
||||
nb_heap_peek/3,
|
||||
nb_heap_empty/1,
|
||||
nb_heap_size/2,
|
||||
nb_beam/2,
|
||||
nb_beam_close/1,
|
||||
nb_beam_add/3,
|
||||
nb_beam_del/3,
|
||||
nb_beam_peek/3,
|
||||
nb_beam_empty/1,
|
||||
% nb_beam_check/1,
|
||||
nb_beam_size/2]).
|
||||
|
||||
/** @defgroup nb Non-Backtrackable Data Structures
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -188,31 +228,3 @@ Unify _Size_ with the number of elements in the queue _Queue_.
|
||||
|
||||
|
||||
*/
|
||||
:- module(nb, [
|
||||
nb_create_accumulator/2,
|
||||
nb_add_to_accumulator/2,
|
||||
nb_accumulator_value/2,
|
||||
nb_queue/1,
|
||||
nb_queue/2,
|
||||
nb_queue_close/3,
|
||||
nb_queue_enqueue/2,
|
||||
nb_queue_dequeue/2,
|
||||
nb_queue_peek/2,
|
||||
nb_queue_empty/1,
|
||||
nb_queue_size/2,
|
||||
nb_queue_replace/3,
|
||||
nb_heap/2,
|
||||
nb_heap_close/1,
|
||||
nb_heap_add/3,
|
||||
nb_heap_del/3,
|
||||
nb_heap_peek/3,
|
||||
nb_heap_empty/1,
|
||||
nb_heap_size/2,
|
||||
nb_beam/2,
|
||||
nb_beam_close/1,
|
||||
nb_beam_add/3,
|
||||
nb_beam_del/3,
|
||||
nb_beam_peek/3,
|
||||
nb_beam_empty/1,
|
||||
% nb_beam_check/1,
|
||||
nb_beam_size/2]).
|
||||
|
@@ -1,26 +1,42 @@
|
||||
/**
|
||||
* @file ordsets.yap
|
||||
* @author : R.A.O'Keefe
|
||||
* @date 22 May 1983
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date 1999
|
||||
* @brief
|
||||
*
|
||||
*
|
||||
*/
|
||||
% This file has been included as an YAP library by Vitor Santos Costa, 1999
|
||||
|
||||
% File : ORDSET.PL
|
||||
% Author : R.A.O'Keefe
|
||||
% Updated: 22 May 1983
|
||||
% Purpose: Ordered set manipulation utilities
|
||||
|
||||
% In this module, sets are represented by ordered lists with no
|
||||
% duplicates. Thus {c,r,a,f,t} would be [a,c,f,r,t]. The ordering
|
||||
% is defined by the @< family of term comparison predicates, which
|
||||
% is the ordering used by sort/2 and setof/3.
|
||||
|
||||
% The benefit of the ordered representation is that the elementary
|
||||
% set operations can be done in time proportional to the Sum of the
|
||||
% argument sizes rather than their Product. Some of the unordered
|
||||
% set routines, such as member/2, length/2, select/3 can be used
|
||||
% unchanged. The main difficulty with the ordered representation is
|
||||
% remembering to use it!
|
||||
|
||||
:- module(ordsets, [
|
||||
list_to_ord_set/2, % List -> Set
|
||||
merge/3, % OrdList x OrdList -> OrdList
|
||||
ord_add_element/3, % Set x Elem -> Set
|
||||
ord_del_element/3, % Set x Elem -> Set
|
||||
ord_disjoint/2, % Set x Set ->
|
||||
ord_insert/3, % Set x Elem -> Set
|
||||
ord_member/2, % Set -> Elem
|
||||
ord_intersect/2, % Set x Set ->
|
||||
ord_intersect/3, % Set x Set -> Set
|
||||
ord_intersection/3, % Set x Set -> Set
|
||||
ord_intersection/4, % Set x Set -> Set x Set
|
||||
ord_seteq/2, % Set x Set ->
|
||||
ord_setproduct/3, % Set x Set -> Set
|
||||
ord_subset/2, % Set x Set ->
|
||||
ord_subtract/3, % Set x Set -> Set
|
||||
ord_symdiff/3, % Set x Set -> Set
|
||||
ord_union/2, % Set^2 -> Set
|
||||
ord_union/3, % Set x Set -> Set
|
||||
ord_union/4, % Set x Set -> Set x Set,
|
||||
ord_empty/1, % -> Set
|
||||
ord_memberchk/2 % Element X Set
|
||||
]).
|
||||
|
||||
/** @defgroup Ordered_Sets Ordered Sets
|
||||
@ingroup library
|
||||
@{
|
||||
* @ingroup library
|
||||
* @{
|
||||
|
||||
The following ordered set manipulation routines are available once
|
||||
included with the `use_module(library(ordsets))` command. An
|
||||
@@ -29,29 +45,22 @@ elements. Output arguments are guaranteed to be ordered sets, if the
|
||||
relevant inputs are. This is a slightly patched version of Richard
|
||||
O'Keefe's original library.
|
||||
|
||||
|
||||
In this module, sets are represented by ordered lists with no
|
||||
duplicates. Thus {c,r,a,f,t} would be [a,c,f,r,t]. The ordering
|
||||
is defined by the @< family of term comparison predicates, which
|
||||
is the ordering used by sort/2 and setof/3.
|
||||
|
||||
The benefit of the ordered representation is that the elementary
|
||||
set operations can be done in time proportional to the Sum of the
|
||||
argument sizes rather than their Product. Some of the unordered
|
||||
set routines, such as member/2, length/2, select/3 can be used
|
||||
unchanged. The main difficulty with the ordered representation is
|
||||
remembering to use it!
|
||||
|
||||
|
||||
*/
|
||||
|
||||
|
||||
/** @pred list_to_ord_set(+ _List_, ? _Set_)
|
||||
|
||||
|
||||
Holds when _Set_ is the ordered representation of the set
|
||||
represented by the unordered representation _List_.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred merge(+ _List1_, + _List2_, - _Merged_)
|
||||
|
||||
|
||||
Holds when _Merged_ is the stable merge of the two given lists.
|
||||
|
||||
Notice that merge/3 will not remove duplicates, so merging
|
||||
ordered sets will not necessarily result in an ordered set. Use
|
||||
`ord_union/3` instead.
|
||||
|
||||
|
||||
*/
|
||||
/** @pred ord_add_element(+ _Set1_, + _Element_, ? _Set2_)
|
||||
|
||||
|
||||
@@ -173,29 +182,6 @@ Holds when _Union_ is the union of the lists _Sets_.
|
||||
|
||||
|
||||
*/
|
||||
:- module(ordsets, [
|
||||
list_to_ord_set/2, % List -> Set
|
||||
merge/3, % OrdList x OrdList -> OrdList
|
||||
ord_add_element/3, % Set x Elem -> Set
|
||||
ord_del_element/3, % Set x Elem -> Set
|
||||
ord_disjoint/2, % Set x Set ->
|
||||
ord_insert/3, % Set x Elem -> Set
|
||||
ord_member/2, % Set -> Elem
|
||||
ord_intersect/2, % Set x Set ->
|
||||
ord_intersect/3, % Set x Set -> Set
|
||||
ord_intersection/3, % Set x Set -> Set
|
||||
ord_intersection/4, % Set x Set -> Set x Set
|
||||
ord_seteq/2, % Set x Set ->
|
||||
ord_setproduct/3, % Set x Set -> Set
|
||||
ord_subset/2, % Set x Set ->
|
||||
ord_subtract/3, % Set x Set -> Set
|
||||
ord_symdiff/3, % Set x Set -> Set
|
||||
ord_union/2, % Set^2 -> Set
|
||||
ord_union/3, % Set x Set -> Set
|
||||
ord_union/4, % Set x Set -> Set x Set,
|
||||
ord_empty/1, % -> Set
|
||||
ord_memberchk/2 % Element X Set
|
||||
]).
|
||||
|
||||
/*
|
||||
:- mode
|
||||
@@ -221,7 +207,7 @@ Holds when _Union_ is the union of the lists _Sets_.
|
||||
*/
|
||||
|
||||
|
||||
% list_to_ord_set(+List, ?Set)
|
||||
%% @pred list_to_ord_set(+List, ?Set)
|
||||
% is true when Set is the ordered representation of the set represented
|
||||
% by the unordered representation List. The only reason for giving it
|
||||
% a name at all is that you may not have realised that sort/2 could be
|
||||
@@ -231,7 +217,7 @@ list_to_ord_set(List, Set) :-
|
||||
sort(List, Set).
|
||||
|
||||
|
||||
% merge(+List1, +List2, -Merged)
|
||||
%% @ored merge(+List1, +List2, -Merged)
|
||||
% is true when Merged is the stable merge of the two given lists.
|
||||
% If the two lists are not ordered, the merge doesn't mean a great
|
||||
% deal. Merging is perfectly well defined when the inputs contain
|
||||
@@ -250,7 +236,7 @@ merge(List1, [], List1).
|
||||
|
||||
|
||||
|
||||
% ord_disjoint(+Set1, +Set2)
|
||||
%% @ored ord_disjoint(+Set1, +Set2)
|
||||
% is true when the two ordered sets have no element in common. If the
|
||||
% arguments are not ordered, I have no idea what happens.
|
||||
|
||||
@@ -267,7 +253,7 @@ ord_disjoint(>, Head1, Tail1, _, Tail2) :-
|
||||
|
||||
|
||||
|
||||
% ord_insert(+Set1, +Element, ?Set2)
|
||||
%% @ored ord_insert(+Set1, +Element, ?Set2)
|
||||
% ord_add_element(+Set1, +Element, ?Set2)
|
||||
% is the equivalent of add_element for ordered sets. It should give
|
||||
% exactly the same result as merge(Set1, [Element], Set2), but a bit
|
||||
@@ -292,7 +278,7 @@ ord_insert(>, Head, Tail, Element, [Element,Head|Tail]).
|
||||
|
||||
|
||||
|
||||
% ord_intersect(+Set1, +Set2)
|
||||
%% @pred ord_intersect(+Set1, +Set2)
|
||||
% is true when the two ordered sets have at least one element in common.
|
||||
% Note that the test is == rather than = .
|
||||
|
||||
@@ -310,7 +296,7 @@ ord_intersect(L1, L2, L) :-
|
||||
ord_intersection(L1, L2, L).
|
||||
|
||||
|
||||
% ord_intersection(+Set1, +Set2, ?Intersection)
|
||||
%% @pred ord_intersection(+Set1, +Set2, ?Intersection)
|
||||
% is true when Intersection is the ordered representation of Set1
|
||||
% and Set2, provided that Set1 and Set2 are ordered sets.
|
||||
|
||||
@@ -327,7 +313,7 @@ ord_intersection([Head1|Tail1], [Head2|Tail2], Intersection) :-
|
||||
ord_intersection([Head1|Tail1], Tail2, Intersection)
|
||||
).
|
||||
|
||||
% ord_intersection(+Set1, +Set2, ?Intersection, ?Difference)
|
||||
%% @pred ord_intersection(+Set1, +Set2, ?Intersection, ?Difference)
|
||||
% is true when Intersection is the ordered representation of Set1
|
||||
% and Set2, provided that Set1 and Set2 are ordered sets.
|
||||
|
||||
@@ -408,7 +394,7 @@ ord_del_element(>, Head1, Tail1, _, [Head1|Tail1]).
|
||||
|
||||
|
||||
|
||||
% ord_symdiff(+Set1, +Set2, ?Difference)
|
||||
%% @pred ord_symdiff(+Set1, +Set2, ?Difference)
|
||||
% is true when Difference is the symmetric difference of Set1 and Set2.
|
||||
|
||||
ord_symdiff(Set1, [], Set1) :- !.
|
||||
@@ -444,7 +430,7 @@ ord_union(>, Head1, Tail1, Head2, Tail2, [Head2|Union]) :-
|
||||
ord_union([Head1|Tail1], Tail2, Union).
|
||||
|
||||
|
||||
% ord_union(+Set1, +Set2, ?Union, ?Difference)
|
||||
%% @pred ord_union(+Set1, +Set2, ?Union, ?Difference)
|
||||
% is true when Union is the union of Set1 and Set2 and Difference is the
|
||||
% difference between Set2 and Set1.
|
||||
|
||||
@@ -463,7 +449,7 @@ ord_union(>, Head1, Tail1, Head2, Tail2, [Head2|Union], [Head2|Diff]) :-
|
||||
|
||||
|
||||
|
||||
% ord_setproduct(+Set1, +Set2, ?Product)
|
||||
%% @pred ord_setproduct(+Set1, +Set2, ?Product)
|
||||
% is in fact identical to setproduct(Set1, Set2, Product).
|
||||
% If Set1 and Set2 are ordered sets, Product will be an ordered
|
||||
% set of x1-x2 pairs. Note that we cannot solve for Set1 and
|
||||
|
@@ -1,3 +1,12 @@
|
||||
/**
|
||||
* @file parameters.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 23:34:04 2015
|
||||
*
|
||||
* @brief Experimental test generation code.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module( parameters,
|
||||
[such_that/2,
|
||||
@@ -17,9 +26,8 @@
|
||||
%%! @{
|
||||
|
||||
/**
|
||||
@file parameters.yap
|
||||
@defgroup parameter Automating test generation
|
||||
@ingroup library
|
||||
* @defgroup parameters Automating test generation
|
||||
* @ingroup library
|
||||
|
||||
This library aims at facilitating test generation in a logic
|
||||
program, namely when interfacing to foreign code. It introduces the
|
||||
|
@@ -16,17 +16,34 @@
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
@groupdef PseudoRandom Van Gelder Random Number Generator
|
||||
@ingroup builtins
|
||||
@{
|
||||
* @file prandom.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Tue Nov 17 23:43:18 2015
|
||||
*
|
||||
* @brief Van Gelder Random Number Generator
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(prandom, [
|
||||
ranstart/0,
|
||||
ranstart/1,
|
||||
rannum/1,
|
||||
ranunif/2]).
|
||||
|
||||
|
||||
%%
|
||||
% @groupdef prandom Van Gelder Random Number Generator
|
||||
% @ingroup builtins
|
||||
% @{
|
||||
%
|
||||
%
|
||||
% The following code produces the same random numbers as my previous
|
||||
% ranpkg.pl, but is more accurately documented and slightly more
|
||||
% efficient.
|
||||
|
||||
%
|
||||
% ranpkg.pl random number package Allen Van Gelder, Stanford
|
||||
|
||||
vvvvvv
|
||||
% rannum produces a random non-negative integer whose low bits are not
|
||||
% all that random, so it should be scaled to a smaller range in general.
|
||||
% The integer is in the range 0 .. 2^(w-1) - 1,
|
||||
@@ -89,12 +106,6 @@ the result is in 0 .. _R_-1.
|
||||
|
||||
|
||||
*/
|
||||
:- module(prandom, [
|
||||
ranstart/0,
|
||||
ranstart/1,
|
||||
rannum/1,
|
||||
ranunif/2]).
|
||||
|
||||
:- initialization(ranstart).
|
||||
|
||||
:- dynamic ranState/5.
|
||||
@@ -107,7 +118,7 @@ wsize(32) :-
|
||||
yap_flag(max_tagged_integer,I), I >> 32 =:= 0, !.
|
||||
wsize(64).
|
||||
|
||||
ranstart :- ranstart(8'365).
|
||||
ranstart :- ranstart(8'365). %
|
||||
|
||||
ranstart(N) :-
|
||||
wsize(Wsize), % bits available for int.
|
||||
|
@@ -1,12 +1,31 @@
|
||||
% This file has been included as an YAP library by Vitor Santos Costa, 1999
|
||||
/**
|
||||
* @file queues.yap
|
||||
* @author R.A.O'Keefe
|
||||
* @date Friday November 18th, 1983, 8:09:31
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date 1999-
|
||||
*
|
||||
* @brief define queue operations
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
% File : QUEUES.PL
|
||||
% Author : R.A.O'Keefe
|
||||
% Updated: Friday November 18th, 1983, 8:09:31 pm
|
||||
% Purpose: define queue operations
|
||||
% Needs : lib(lists) for append/3.
|
||||
:- module(queues, [
|
||||
make_queue/1, % create empty queue
|
||||
join_queue/3, % add element to end of queue
|
||||
list_join_queue/3, % add many elements to end of queue
|
||||
jump_queue/3, % add element to front of queue
|
||||
list_jump_queue/3, % add many elements to front of queue
|
||||
head_queue/2, % look at first element of queue
|
||||
serve_queue/3, % remove first element of queue
|
||||
length_queue/2, % count elements of queue
|
||||
empty_queue/1, % test whether queue is empty
|
||||
list_to_queue/2, % convert list to queue
|
||||
queue_to_list/2 % convert queue to list
|
||||
]).
|
||||
|
||||
/** @defgroup Queues Queues
|
||||
|
||||
/** @defgroup queues Queues
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -14,6 +33,19 @@ The following queue manipulation routines are available once
|
||||
included with the `use_module(library(queues))` command. Queues are
|
||||
implemented with difference lists.
|
||||
|
||||
In this package, a queue is represented as a term Front-Back, where
|
||||
Front is a list and Back is a tail of that list, and is normally a
|
||||
variable. join_queue will only work when the Back is a variable,
|
||||
the other routines will accept any tail. The elements of the queue
|
||||
are the list difference, that is, all the elements starting at Front
|
||||
and stopping at Back. Examples:
|
||||
|
||||
[a,b,c,d,e|Z]-Z has elements a,b,c,d,e
|
||||
[a,b,c,d,e]-[d,e] has elements a,b,c
|
||||
Z-Z has no elements
|
||||
[1,2,3]-[1,2,3] has no elements
|
||||
|
||||
|
||||
*/
|
||||
|
||||
/**
|
||||
@@ -99,20 +131,6 @@ Removes the first element of the queue for service.
|
||||
|
||||
|
||||
*/
|
||||
:- module(queues, [
|
||||
make_queue/1, % create empty queue
|
||||
join_queue/3, % add element to end of queue
|
||||
list_join_queue/3, % add many elements to end of queue
|
||||
jump_queue/3, % add element to front of queue
|
||||
list_jump_queue/3, % add many elements to front of queue
|
||||
head_queue/2, % look at first element of queue
|
||||
serve_queue/3, % remove first element of queue
|
||||
length_queue/2, % count elements of queue
|
||||
empty_queue/1, % test whether queue is empty
|
||||
list_to_queue/2, % convert list to queue
|
||||
queue_to_list/2 % convert queue to list
|
||||
]).
|
||||
|
||||
:- use_module(library(lists), [append/3]).
|
||||
|
||||
/*
|
||||
@@ -132,19 +150,6 @@ Removes the first element of the queue for service.
|
||||
queue_to_list(+, +, -).
|
||||
*/
|
||||
|
||||
/* In this package, a queue is represented as a term Front-Back, where
|
||||
Front is a list and Back is a tail of that list, and is normally a
|
||||
variable. join_queue will only work when the Back is a variable,
|
||||
the other routines will accept any tail. The elements of the queue
|
||||
are the list difference, that is, all the elements starting at Front
|
||||
and stopping at Back. Examples:
|
||||
|
||||
[a,b,c,d,e|Z]-Z has elements a,b,c,d,e
|
||||
[a,b,c,d,e]-[d,e] has elements a,b,c
|
||||
Z-Z has no elements
|
||||
[1,2,3]-[1,2,3] has no elements
|
||||
*/
|
||||
|
||||
% make_queue(Queue)
|
||||
% creates a new empty queue. It will also match empty queues, but
|
||||
% because Prolog doesn't do the occurs check, it will also match
|
||||
|
@@ -15,25 +15,46 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
% original code from RA O'Keefe.
|
||||
/**
|
||||
* @file random.yap
|
||||
* @author original code from RA O'Keefe.
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Wed Nov 18 00:05:21 2015
|
||||
*
|
||||
* @brief Integer Random Number Generator
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
% This is algorithm AS 183 from Applied Statistics. I also have a C
|
||||
% version. It is really very good. It is straightforward to make a
|
||||
% version which yields 15-bit random integers using only integer
|
||||
% arithmetic.
|
||||
|
||||
/** @defgroup Pseudo_Random Random Number Generator
|
||||
:- module(random, [
|
||||
random/1,
|
||||
random/3,
|
||||
randseq/3,
|
||||
randset/3,
|
||||
getrand/1,
|
||||
setrand/1
|
||||
]).
|
||||
|
||||
/** @defgroup random Random Number Generator
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
The following random number operations are included with the
|
||||
`use_module(library(random))` command. Since YAP-4.3.19 YAP uses
|
||||
Since YAP-4.3.19 YAP uses
|
||||
the O'Keefe public-domain algorithm, based on the "Applied Statistics"
|
||||
algorithm AS183.
|
||||
|
||||
The following random number operations are included with the
|
||||
`use_module(library(random))` command.
|
||||
|
||||
In ROK's words: ``This is algorithm AS 183 from Applied Statistics. I also have a C
|
||||
version. It is really very good. It is straightforward to make a
|
||||
version which yields 15-bit random integers using only integer
|
||||
arithmetic.''
|
||||
|
||||
|
||||
@pred getrand(- _Key_)
|
||||
*/
|
||||
|
||||
/** @pred getrand(- _Key_)
|
||||
|
||||
|
||||
Unify _Key_ with a term of the form `rand(X,Y,Z)` describing the
|
||||
@@ -104,15 +125,6 @@ random number generator. The integer `X` must be in the range
|
||||
|
||||
|
||||
*/
|
||||
:- module(random, [
|
||||
random/1,
|
||||
random/3,
|
||||
randseq/3,
|
||||
randset/3,
|
||||
getrand/1,
|
||||
setrand/1
|
||||
]).
|
||||
|
||||
:- use_module(library(pairs)).
|
||||
:- use_module(library(error)).
|
||||
:- use_module(library(lists)).
|
||||
|
@@ -15,6 +15,16 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
* @file range.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Wed Nov 18 00:10:17 2015
|
||||
*
|
||||
* @brief stub for geometry operations.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(range, [
|
||||
euclidean_distance/3,
|
||||
in_range/4,
|
||||
|
@@ -1,13 +1,12 @@
|
||||
/*
|
||||
|
||||
This code implements Red-Black trees as described in:
|
||||
|
||||
"Introduction to Algorithms", Second Edition
|
||||
Cormen, Leiserson, Rivest, and Stein,
|
||||
MIT Press
|
||||
|
||||
Author: Vitor Santos Costa
|
||||
|
||||
/**
|
||||
* @file rbtrees.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @author Jan Wielemaker
|
||||
* @date Wed Nov 18 00:11:41 2015
|
||||
*
|
||||
* @brief Red-Black trees
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
@@ -53,9 +52,8 @@
|
||||
%%! @{
|
||||
|
||||
/**
|
||||
@file rbtrees.yap
|
||||
@defgroup rbtrees Red-Black Trees
|
||||
@ingroup library
|
||||
* @defgroup rbtrees Red-Black Trees
|
||||
* @ingroup library
|
||||
|
||||
Red-Black trees are balanced search binary trees. They are named because
|
||||
nodes can be classified as either red or black. The code we include is
|
||||
|
@@ -15,6 +15,16 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
* @file readutil.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Wed Nov 18 00:16:15 2015
|
||||
*
|
||||
* @brief Read full lines and a full file in a single call.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(readutil, [
|
||||
read_line_to_codes/2,
|
||||
read_line_to_codes/3,
|
||||
@@ -27,6 +37,14 @@
|
||||
read_line_to_string/2
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defsgroup readutil
|
||||
* @ingroup library
|
||||
*
|
||||
* Read full lines and a full file in a single call.
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
read_stream_to_codes(Stream, Codes) :-
|
||||
read_stream_to_codes(Stream, Codes, []).
|
||||
@@ -37,6 +55,7 @@ read_file_to_codes(File, Codes, _) :-
|
||||
close(Stream).
|
||||
|
||||
read_file_to_codes(File, Codes) :-
|
||||
v
|
||||
open(File, read, Stream),
|
||||
read_stream_to_codes(Stream, Codes, []),
|
||||
close(Stream).
|
||||
|
@@ -15,7 +15,24 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/** @defgroup RegExp Regular Expressions
|
||||
/**
|
||||
* @file regexp.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Wed Nov 18 00:27:52 2015
|
||||
*
|
||||
* @brief Support for Regular Expressions in YAP
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(regexp, [
|
||||
regexp/3,
|
||||
regexp/4
|
||||
]).
|
||||
|
||||
|
||||
/** @defgroup regexp Regular Expressions
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -147,11 +164,6 @@ sub-expression. Thus the `"b"` has already been claimed before the
|
||||
|
||||
|
||||
*/
|
||||
:- module(regexp, [
|
||||
regexp/3,
|
||||
regexp/4
|
||||
]).
|
||||
|
||||
:- load_foreign_files([regexp], [], init_regexp).
|
||||
|
||||
regexp(RegExp, String, Opts) :-
|
||||
|
@@ -1,9 +1,12 @@
|
||||
/****************************************
|
||||
File: rltree.yap
|
||||
Author: Nuno A. Fonseca
|
||||
Comments: Range-List (RL) tree data structure implementation for YAP
|
||||
version: $Id: rltree.yap,v 1.1 2008-03-26 23:05:22 nunofonseca Exp $
|
||||
****************************************/
|
||||
/**
|
||||
* @file rltree.yap
|
||||
* @author Nuno A. Fonseca
|
||||
* @date 2008-03-26 23:05:22
|
||||
*
|
||||
* @brief Range-List (RL) tree data structure implementation for YAP
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(rltree, [
|
||||
rl_new/2, %% (+Maximum Interval value, -Range-List Id)
|
||||
@@ -18,4 +21,15 @@
|
||||
rl_freeze/1 %%(+Range-List Id)
|
||||
]).
|
||||
|
||||
|
||||
/**
|
||||
* @defgroup rltrees
|
||||
* @ingroup library
|
||||
*
|
||||
* Range-List (RL) tree data structure implementation for YAP
|
||||
*/
|
||||
|
||||
|
||||
|
||||
|
||||
:- load_foreign_files([yap_rl], [], init_rl).
|
||||
|
@@ -41,11 +41,11 @@ unsigned long int tree_mem=0;
|
||||
#define FREE_MEM_USAGE(tree) (memory_usage-=tree->mem_alloc)
|
||||
#define ADD_MEM_USAGE(tree) (memory_usage+=tree->mem_alloc)
|
||||
|
||||
/*
|
||||
/** @pred rl_new( ? Size, ? Tree).
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_new(void) {
|
||||
rl_new(void) {
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
YAP_Term t2=YAP_Deref(YAP_ARG2);
|
||||
RL_Tree* new_tree;
|
||||
@@ -70,13 +70,13 @@ p_rl_new(void) {
|
||||
|
||||
return(TRUE);
|
||||
}
|
||||
/*
|
||||
*
|
||||
/* @pred rl_new( ? OldTree, ? NewTree).
|
||||
*
|
||||
* copy from old tree to mew tree
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_copy(void) {
|
||||
rl_copy(void) {
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1); // src
|
||||
YAP_Term t2=YAP_Deref(YAP_ARG2); // dest
|
||||
RL_Tree* new_tree;
|
||||
@@ -108,13 +108,13 @@ p_rl_copy(void) {
|
||||
return (FALSE);
|
||||
return(TRUE);
|
||||
}
|
||||
/*
|
||||
*
|
||||
/** @pred rl_size( ? Tree, ? Size).
|
||||
*
|
||||
*
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_size(void) {
|
||||
rl_size(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1),t_size;
|
||||
IDTYPE id;
|
||||
@@ -134,13 +134,13 @@ p_rl_size(void) {
|
||||
|
||||
return(TRUE);
|
||||
}
|
||||
/*
|
||||
/** @pred rl_new( ? AllTrees ).
|
||||
*
|
||||
*
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_mem_usage(void) {
|
||||
rl_mem_usage(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
|
||||
@@ -150,11 +150,11 @@ p_rl_mem_usage(void) {
|
||||
return(TRUE);
|
||||
}
|
||||
|
||||
/*
|
||||
/** @pred rl_free( ? Tree).
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_free(void) {
|
||||
rl_free(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
IDTYPE id;
|
||||
@@ -176,12 +176,12 @@ p_rl_free(void) {
|
||||
}
|
||||
|
||||
/*
|
||||
*
|
||||
* @pred rl_set_in( + Tree, +Value )
|
||||
*
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_set_in(void) {
|
||||
rl_set_in(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
YAP_Term t2=YAP_Deref(YAP_ARG2);
|
||||
@@ -215,7 +215,7 @@ p_rl_set_in(void) {
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_in(void) {
|
||||
rl_in(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
YAP_Term t2=YAP_Deref(YAP_ARG2);
|
||||
@@ -238,13 +238,13 @@ p_rl_in(void) {
|
||||
}
|
||||
#endif
|
||||
|
||||
/*
|
||||
/*@pred rl_free( ? Tree).
|
||||
*
|
||||
*
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_set_out(void) {
|
||||
rl_set_out(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
YAP_Term t2=YAP_Deref(YAP_ARG2);
|
||||
@@ -275,7 +275,7 @@ p_rl_set_out(void) {
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_freeze(void) {
|
||||
rl_freeze(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
IDTYPE id;
|
||||
@@ -299,13 +299,14 @@ p_rl_freeze(void) {
|
||||
|
||||
return (TRUE);
|
||||
}
|
||||
/*
|
||||
*
|
||||
/** @pred rl_set_all( + Tree, Els).
|
||||
* @addrogroup rl
|
||||
*
|
||||
*/
|
||||
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_set_all_in(void) {
|
||||
rl_set_all_in(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
IDTYPE id;
|
||||
@@ -331,13 +332,13 @@ p_rl_set_all_in(void) {
|
||||
|
||||
return (TRUE);
|
||||
}
|
||||
/*
|
||||
/** @pred rl_print( + Tree).
|
||||
*
|
||||
*
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_print(void) {
|
||||
rl_print(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
IDTYPE id;
|
||||
@@ -373,7 +374,7 @@ yap_back_data_type *back_data;
|
||||
*/
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_b_in2(void) {
|
||||
rl_b_in2(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
IDTYPE id;
|
||||
@@ -394,7 +395,7 @@ p_rl_b_in2(void) {
|
||||
}
|
||||
static
|
||||
YAP_Bool
|
||||
p_rl_b_in1(void) {
|
||||
rl_b_in1(void) {
|
||||
|
||||
YAP_Term t1=YAP_Deref(YAP_ARG1);
|
||||
YAP_Term t2=YAP_Deref(YAP_ARG2);
|
||||
@@ -411,7 +412,7 @@ p_rl_b_in1(void) {
|
||||
// return all in through backtracking
|
||||
YAP_PRESERVE_DATA(back_data,yap_back_data_type);
|
||||
back_data->last_solution = YAP_MkIntTerm(0);
|
||||
return p_rl_b_in2();
|
||||
return rl_b_in2();
|
||||
} else {
|
||||
id = YAP_IntOfTerm(t1);
|
||||
tree=ID2PTR(id);
|
||||
@@ -430,21 +431,21 @@ void init_rl(void);
|
||||
void init_rl(void){
|
||||
|
||||
|
||||
YAP_UserCPredicate("rl_new", p_rl_new,2); // Maximum -> RangeID
|
||||
YAP_UserCPredicate("rl_free", p_rl_free,1); // RangeId ->
|
||||
YAP_UserCPredicate("rl_size", p_rl_size,2); // RangeId -> Size (in bytes)
|
||||
YAP_UserCPredicate("rl_mem", p_rl_mem_usage,1); // -> TotalMemory (in bytes)
|
||||
YAP_UserCPredicate("rl_new", rl_new,2); // Maximum -> RangeID
|
||||
YAP_UserCPredicate("rl_free", rl_free,1); // RangeId ->
|
||||
YAP_UserCPredicate("rl_size", rl_size,2); // RangeId -> Size (in bytes)
|
||||
YAP_UserCPredicate("rl_mem", rl_mem_usage,1); // -> TotalMemory (in bytes)
|
||||
|
||||
YAP_UserCPredicate("rl_copy", p_rl_copy,2); // RangeId -> NewRangeId
|
||||
YAP_UserCPredicate("rl_set_out", p_rl_set_out,2);// RangeId x Number ->
|
||||
YAP_UserBackCPredicate("rl_in", p_rl_b_in1,p_rl_b_in2,2,sizeof(yap_back_data_type)); // +RangeId x ?Number
|
||||
//YAP_UserCPredicate("rl_in", p_rl_in,2); // RangeId x Number ->
|
||||
YAP_UserCPredicate("rl_set_in", p_rl_set_in,2); // RangeIdxNumber ->
|
||||
YAP_UserCPredicate("rl_set_all_in", p_rl_set_all_in,1); // RangeId ->
|
||||
YAP_UserCPredicate("rl_copy", rl_copy,2); // RangeId -> NewRangeId
|
||||
YAP_UserCPredicate("rl_set_out", rl_set_out,2);// RangeId x Number ->
|
||||
YAP_UserBackCPredicate("rl_in", rl_b_in1,rl_b_in2,2,sizeof(yap_back_data_type)); // +RangeId x ?Number
|
||||
//YAP_UserCPredicate("rl_in", rl_in,2); // RangeId x Number ->
|
||||
YAP_UserCPredicate("rl_set_in", rl_set_in,2); // RangeIdxNumber ->
|
||||
YAP_UserCPredicate("rl_set_all_in", rl_set_all_in,1); // RangeId ->
|
||||
|
||||
YAP_UserCPredicate("rl_print", p_rl_print,1); // RangeId ->
|
||||
YAP_UserCPredicate("rl_print", rl_print,1); // RangeId ->
|
||||
|
||||
YAP_UserCPredicate("rl_freeze", p_rl_freeze,1); // RangeId
|
||||
YAP_UserCPredicate("rl_freeze", rl_freeze,1); // RangeId
|
||||
|
||||
// fprintf(stderr,"Range list module succesfully loaded.");
|
||||
//fflush(stderr);
|
||||
|
@@ -15,6 +15,24 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
* @file splay.yap
|
||||
* @author Vijay Saraswat
|
||||
* @date Wed Nov 18 01:12:49 2015
|
||||
*
|
||||
* @brief "Self-adjusting Binary Search Trees
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(splay,[
|
||||
splay_access/5,
|
||||
splay_insert/4,
|
||||
splay_del/3,
|
||||
splay_init/1,
|
||||
splay_join/3,
|
||||
splay_split/5]).
|
||||
|
||||
/** @defgroup Splay_Trees Splay Trees
|
||||
@ingroup library
|
||||
@{
|
||||
@@ -24,15 +42,93 @@ Trees", by D.D. Sleator and R.E. Tarjan, JACM, vol. 32, No.3, July 1985,
|
||||
p. 668. They are designed to support fast insertions, deletions and
|
||||
removals in binary search trees without the complexity of traditional
|
||||
balanced trees. The key idea is to allow the tree to become
|
||||
unbalanced. To make up for this, whenever we find a node, we move it up
|
||||
unbalanced. To make up for this, whenever we \ find a node, we move it up
|
||||
to the top. We use code by Vijay Saraswat originally posted to the Prolog
|
||||
mailing-list.
|
||||
|
||||
Date: Sun 22 Mar 87 03:40:22-EST
|
||||
>From: vijay <Vijay.Saraswat@C.CS.CMU.EDU>
|
||||
Subject: Splay trees in LP languages.
|
||||
|
||||
There have hardly been any interesting programs in this Digest for a
|
||||
long while now. Here is something which may stir the slothful among
|
||||
you! I present Prolog programs for implementing self-adjusting binary
|
||||
search trees, using splaying. These programs should be among the most
|
||||
efficient Prolog programs for maintaining binary search trees, with
|
||||
dynamic insertion and deletion.
|
||||
|
||||
The algorithm is taken from: "Self-adjusting Binary Search Trees",
|
||||
D.D. Sleator and R.E. Tarjan, JACM, vol. 32, No.3, July 1985, p. 668.
|
||||
(See Tarjan's Turing Award lecture in this month's CACM for a more
|
||||
informal introduction).
|
||||
-----------------------------------------
|
||||
|
||||
The operations provided by the program are:
|
||||
|
||||
1. access(i,t): (implemented by the call access(V, I, T, New))
|
||||
"If item i is in tree t, return a pointer to its location;
|
||||
otherwise return a pointer to the null node."
|
||||
In our implementation, in the call access(V, I, T, New),
|
||||
V is unifies with `null' if the item is not there, else
|
||||
with `true' if it is there, in which case I is also
|
||||
unified with that item.
|
||||
|
||||
2. insert(i,t): (implemented by the call insert(I, T, New))
|
||||
"Insert item i in tree t, assuming that it is not there already."
|
||||
(In our implementation, i is not inserted if it is already
|
||||
there: rather it is unified with the item already in the tree.)
|
||||
|
||||
3. delete(i,t): (implemented by the call del(I, T, New))
|
||||
"Delete item i from tree t, assuming that it is present."
|
||||
(In our implementation, the call fails if the item is not in
|
||||
the tree.)
|
||||
|
||||
4. join(t1,t2): (Implemented by the call join(T1, T2, New))
|
||||
"Combine trees t1 and t2 into a single tree containing
|
||||
all items from both trees, and return the resulting
|
||||
tree. This operation assumes that all items in t1 are
|
||||
less than all those in t2 and destroys both t1 and t2."
|
||||
|
||||
5. split(i,t): (implemented by the call split(I, T, Left, Right))
|
||||
"Construct and return two trees t1 and t2, where t1
|
||||
contains all items in t less than i, and t2 contains all
|
||||
items in t greater than i. This operations destroys t."
|
||||
|
||||
The basic workhorse is the routine bst(Op, Item, Tree, NewTree), which
|
||||
returns in NewTree a binary search tree obtained by searching for Item
|
||||
in< Tree and splaying. OP controls what must happen if Item is not
|
||||
found in the Tree. If Op = access(V), then V is unified with null if
|
||||
the item is not found in the tree, and with true if it is; in the
|
||||
latter case Item is also unified with the item found in the tree. In
|
||||
% the first case, splaying is done at the node at which the discovery
|
||||
% was made that Item was not in the tree, and in the second case
|
||||
% splaying is done at the node at which Item is found. If Op=insert,
|
||||
% then Item is inserted in the tree if it is not found, and splaying is
|
||||
% done at the new node; if the item is found, then splaying is done at
|
||||
% the node at which it is found.
|
||||
|
||||
% A node is simply an n/3 structure: n(NodeValue, LeftSon, RightSon).
|
||||
% NodeValue could be as simple as an integer, or it could be a (Key,
|
||||
% Value) pair.
|
||||
|
||||
|
||||
% A node is simply an n/3 structure: n(NodeValue, LeftSon, RightSon).
|
||||
% NodeValue could be as simple as an integer, or it could be a (Key,
|
||||
% Value) pair.
|
||||
|
||||
% Here are the top-level axioms. The algorithm for del/3 is the first
|
||||
% algorithm mentioned in the JACM paper: namely, first access the
|
||||
% element to be deleted, thus bringing it to the root, and then join its
|
||||
% sons. (join/4 is discussed later.)
|
||||
|
||||
|
||||
|
||||
*/
|
||||
|
||||
/*
|
||||
@pred splay_access(- _Return_,+ _Key_,? _Val_,+ _Tree_,- _NewTree_)
|
||||
|
||||
|
||||
v
|
||||
If item _Key_ is in tree _Tree_, return its _Val_ and
|
||||
unify _Return_ with `true`. Otherwise unify _Return_ with
|
||||
`null`. The variable _NewTree_ unifies with the new tree.
|
||||
@@ -86,93 +182,10 @@ Construct and return two trees _LeftTree_ and _RightTree_,
|
||||
where _LeftTree_ contains all items in _Tree_ less than
|
||||
_Key_, and _RightTree_ contains all items in _Tree_
|
||||
greater than _Key_. This operations destroys _Tree_.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
|
||||
*/
|
||||
:- module(splay,[
|
||||
splay_access/5,
|
||||
splay_insert/4,
|
||||
splay_del/3,
|
||||
splay_init/1,
|
||||
splay_join/3,
|
||||
splay_split/5]).
|
||||
|
||||
% Date: Sun 22 Mar 87 03:40:22-EST
|
||||
% >From: vijay <Vijay.Saraswat@C.CS.CMU.EDU>
|
||||
% Subject: Splay trees in LP languages.
|
||||
|
||||
% There have hardly been any interesting programs in this Digest for a
|
||||
% long while now. Here is something which may stir the slothful among
|
||||
% you! I present Prolog programs for implementing self-adjusting binary
|
||||
% search trees, using splaying. These programs should be among the most
|
||||
% efficient Prolog programs for maintaining binary search trees, with
|
||||
% dynamic insertion and deletion.
|
||||
|
||||
% The algorithm is taken from: "Self-adjusting Binary Search Trees",
|
||||
% D.D. Sleator and R.E. Tarjan, JACM, vol. 32, No.3, July 1985, p. 668.
|
||||
% (See Tarjan's Turing Award lecture in this month's CACM for a more
|
||||
% informal introduction).
|
||||
% -----------------------------------------
|
||||
|
||||
% The operations provided by the program are:
|
||||
|
||||
% 1. access(i,t): (implemented by the call access(V, I, T, New))
|
||||
% "If item i is in tree t, return a pointer to its location;
|
||||
% otherwise return a pointer to the null node."
|
||||
% In our implementation, in the call access(V, I, T, New),
|
||||
% V is unifies with `null' if the item is not there, else
|
||||
% with `true' if it is there, in which case I is also
|
||||
% unified with that item.
|
||||
|
||||
% 2. insert(i,t): (implemented by the call insert(I, T, New))
|
||||
% "Insert item i in tree t, assuming that it is not there already."
|
||||
% (In our implementation, i is not inserted if it is already
|
||||
% there: rather it is unified with the item already in the tree.)
|
||||
|
||||
% 3. delete(i,t): (implemented by the call del(I, T, New))
|
||||
% "Delete item i from tree t, assuming that it is present."
|
||||
% (In our implementation, the call fails if the item is not in
|
||||
% the tree.)
|
||||
|
||||
% 4. join(t1,t2): (Implemented by the call join(T1, T2, New))
|
||||
% "Combine trees t1 and t2 into a single tree containing
|
||||
% all items from both trees, and return the resulting
|
||||
% tree. This operation assumes that all items in t1 are
|
||||
% less than all those in t2 and destroys both t1 and t2."
|
||||
|
||||
% 5. split(i,t): (implemented by the call split(I, T, Left, Right))
|
||||
% "Construct and return two trees t1 and t2, where t1
|
||||
% contains all items in t less than i, and t2 contains all
|
||||
% items in t greater than i. This operations destroys t."
|
||||
|
||||
% The basic workhorse is the routine bst(Op, Item, Tree, NewTree), which
|
||||
% returns in NewTree a binary search tree obtained by searching for Item
|
||||
% in< Tree and splaying. OP controls what must happen if Item is not
|
||||
% found in the Tree. If Op = access(V), then V is unified with null if
|
||||
% the item is not found in the tree, and with true if it is; in the
|
||||
% latter case Item is also unified with the item found in the tree. In
|
||||
% the first case, splaying is done at the node at which the discovery
|
||||
% was made that Item was not in the tree, and in the second case
|
||||
% splaying is done at the node at which Item is found. If Op=insert,
|
||||
% then Item is inserted in the tree if it is not found, and splaying is
|
||||
% done at the new node; if the item is found, then splaying is done at
|
||||
% the node at which it is found.
|
||||
|
||||
% A node is simply an n/3 structure: n(NodeValue, LeftSon, RightSon).
|
||||
% NodeValue could be as simple as an integer, or it could be a (Key,
|
||||
% Value) pair.
|
||||
|
||||
|
||||
% A node is simply an n/3 structure: n(NodeValue, LeftSon, RightSon).
|
||||
% NodeValue could be as simple as an integer, or it could be a (Key,
|
||||
% Value) pair.
|
||||
|
||||
% Here are the top-level axioms. The algorithm for del/3 is the first
|
||||
% algorithm mentioned in the JACM paper: namely, first access the
|
||||
% element to be deleted, thus bringing it to the root, and then join its
|
||||
% sons. (join/4 is discussed later.)
|
||||
|
||||
splay_access(V, Item, Val, Tree, NewTree):-
|
||||
bst(access(V), Item, Val, Tree, NewTree).
|
||||
|
@@ -1,3 +1,12 @@
|
||||
/**
|
||||
* @file stringutils.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Wed Nov 18 01:14:42 2015
|
||||
*
|
||||
* @brief Simple string utilitiities .
|
||||
*
|
||||
*
|
||||
*/
|
||||
:- module(string_utils,
|
||||
[string/1,
|
||||
upcase_string/2,
|
||||
|
@@ -15,17 +15,65 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/** @defgroup System Calling The Operating System from YAP
|
||||
/**
|
||||
* @file system.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Wed Nov 18 01:23:45 2015
|
||||
*
|
||||
* @brief interaction with the OS, be it Unix, Linux, or Windows.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
|
||||
:- module operating_system_support,
|
||||
[
|
||||
delete_file/1,
|
||||
delete_file/2,
|
||||
directory_files/2,
|
||||
environ/2,
|
||||
exec/3,
|
||||
file_exists/1,
|
||||
file_exists/2,
|
||||
file_property/2,
|
||||
host_id/1,
|
||||
host_name/1,
|
||||
kill/1,
|
||||
md5/3,
|
||||
pid/1,
|
||||
mktemp/2,
|
||||
make_directory/1,
|
||||
popen/3,
|
||||
rename_file/2,
|
||||
shell/0,
|
||||
shell/1,
|
||||
shell/2,
|
||||
sleep/1,
|
||||
system/0,
|
||||
system/1,
|
||||
system/2,
|
||||
mktime/2,
|
||||
tmpnam/1,
|
||||
tmp_file/2,
|
||||
tmpdir/1,
|
||||
wait/2,
|
||||
working_directory/2
|
||||
]).
|
||||
|
||||
/** @defgroup operating_system_support, Operating System Functionality
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
YAP now provides a library of system utilities compatible with the
|
||||
YAP provides a library of system utilities compatible with the
|
||||
SICStus Prolog system library. This library extends and to some point
|
||||
replaces the functionality of Operating System access routines. The
|
||||
complements the functionality of Operating System access routines. The
|
||||
library includes Unix/Linux and Win32 `C` code. They
|
||||
are available through the `use_module(library(system))` command.
|
||||
|
||||
*/
|
||||
|
||||
/**
|
||||
|
||||
@pred datime(datime(- _Year_, - _Month_, - _DayOfTheMonth_, - _Hour_, - _Minute_, - _Second_)
|
||||
|
||||
@@ -366,39 +414,6 @@ also `absolute_file_name/2` and chdir/1.
|
||||
|
||||
|
||||
*/
|
||||
:- module(operating_system_support, [
|
||||
datime/1,
|
||||
delete_file/1,
|
||||
delete_file/2,
|
||||
directory_files/2,
|
||||
environ/2,
|
||||
exec/3,
|
||||
file_exists/1,
|
||||
file_exists/2,
|
||||
file_property/2,
|
||||
host_id/1,
|
||||
host_name/1,
|
||||
kill/1,
|
||||
md5/3,
|
||||
pid/1,
|
||||
mktemp/2,
|
||||
make_directory/1,
|
||||
popen/3,
|
||||
rename_file/2,
|
||||
shell/0,
|
||||
shell/1,
|
||||
shell/2,
|
||||
sleep/1,
|
||||
system/0,
|
||||
system/1,
|
||||
system/2,
|
||||
mktime/2,
|
||||
tmpnam/1,
|
||||
tmp_file/2,
|
||||
tmpdir/1,
|
||||
wait/2,
|
||||
working_directory/2
|
||||
]).
|
||||
|
||||
:- use_module(library(lists), [append/3]).
|
||||
|
||||
|
@@ -23,8 +23,8 @@ terms. Most of these utilities have been implemented in `C` for
|
||||
efficiency. They are available through the
|
||||
`use_module(library(terms))` command.
|
||||
|
||||
|
||||
|
||||
*/
|
||||
/**
|
||||
@pred cyclic_term(? _Term_)
|
||||
|
||||
|
||||
|
@@ -15,12 +15,23 @@
|
||||
* *
|
||||
*************************************************************************/
|
||||
|
||||
/**
|
||||
* @file timeout.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date Wed Nov 18 01:26:14 2015
|
||||
*
|
||||
* @brief Calls With Timeout
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- module(timeout, [
|
||||
time_out/3
|
||||
]).
|
||||
|
||||
|
||||
/** @defgroup Timeout Calls With Timeout
|
||||
/** @defgroup timeout Calls With Timeout
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
|
@@ -1,18 +1,53 @@
|
||||
% This file has been included as an YAP library by Vitor Santos Costa, 1999
|
||||
/**
|
||||
* @file trees.yap
|
||||
* @author R.A.O'Keefe
|
||||
This file has been included as an YAP library by Vitor Santos Costa, 1999
|
||||
|
||||
* @date Wed Nov 18 01:30:42 2015
|
||||
*
|
||||
* @brief
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(trees, [
|
||||
get_label/3,
|
||||
list_to_tree/2,
|
||||
map_tree/3,
|
||||
put_label/4,
|
||||
tree_size/2,
|
||||
tree_to_list/2
|
||||
]).
|
||||
|
||||
:- meta_predicate
|
||||
map_tree(2, ?, ?).
|
||||
|
||||
|
||||
|
||||
|
||||
|
||||
%
|
||||
% File : TREES.PL
|
||||
% Author : R.A.O'Keefe
|
||||
% Author :
|
||||
% Updated: 8 November 1983
|
||||
% Purpose: Updatable binary trees.
|
||||
|
||||
/* These are the routines I meant to describe in DAI-WP-150, but the
|
||||
|
||||
/** @defgroup trees Updatable Binary Trees
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
The following queue manipulation routines are available once
|
||||
included with the `use_module(library(trees))` command.
|
||||
|
||||
These are the routines I meant to describe in DAI-WP-150, but the
|
||||
wrong version went in. We have
|
||||
list_to_tree : O(N)
|
||||
tree_to_list : O(N)
|
||||
tree_size : O(N)
|
||||
map_tree : O(N)
|
||||
get_label : O(lg N)
|
||||
put_label : O(lg N)
|
||||
+ list_to_tree : O(N)
|
||||
+ tree_to_list : O(N)
|
||||
+ tree_size : O(N)
|
||||
+ map_tree : O(N)
|
||||
+ get_label : O(lg N)
|
||||
+ put_label : O(lg N)
|
||||
where N is the number of elements in the tree. The way get_label
|
||||
and put_label work is worth noting: they build up a pattern which
|
||||
is matched against the whole tree when the position number finally
|
||||
@@ -23,17 +58,7 @@
|
||||
to match the old tree and a pattern to match the new tree.
|
||||
*/
|
||||
|
||||
|
||||
/** @defgroup Trees Updatable Binary Trees
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
The following queue manipulation routines are available once
|
||||
included with the `use_module(library(trees))` command.
|
||||
|
||||
|
||||
|
||||
@pred get_label(+ _Index_, + _Tree_, ? _Label_)
|
||||
/** @pred get_label(+ _Index_, + _Tree_, ? _Label_)
|
||||
|
||||
|
||||
Treats the tree as an array of _N_ elements and returns the
|
||||
@@ -82,18 +107,6 @@ Is the converse operation to list_to_tree.
|
||||
|
||||
|
||||
*/
|
||||
:- module(trees, [
|
||||
get_label/3,
|
||||
list_to_tree/2,
|
||||
map_tree/3,
|
||||
put_label/4,
|
||||
tree_size/2,
|
||||
tree_to_list/2
|
||||
]).
|
||||
|
||||
:- meta_predicate
|
||||
map_tree(2, ?, ?).
|
||||
|
||||
/*
|
||||
:- mode
|
||||
get_label(+, +, ?),
|
||||
|
@@ -1,3 +1,11 @@
|
||||
/**
|
||||
* @file tries.yap
|
||||
* @author Ricardo Rocha
|
||||
*
|
||||
* @brief
|
||||
*
|
||||
*
|
||||
*/
|
||||
/****************************************
|
||||
File: tries.yap
|
||||
Author: Ricardo Rocha
|
||||
@@ -5,8 +13,53 @@
|
||||
version: $ID$
|
||||
****************************************/
|
||||
|
||||
:- module(tries, [
|
||||
trie_open/1,
|
||||
trie_close/1,
|
||||
trie_close_all/0,
|
||||
trie_empty/1,
|
||||
trie_mode/1,
|
||||
trie_put_entry/3,
|
||||
trie_check_entry/3,
|
||||
trie_get_entry/2,
|
||||
trie_get_first_entry/2,
|
||||
trie_get_last_entry/2,
|
||||
trie_traverse/2,
|
||||
trie_traverse/3,
|
||||
trie_remove_entry/1,
|
||||
trie_remove_subtree/1,
|
||||
trie_join/2,
|
||||
trie_intersect/2,
|
||||
trie_count_join/3,
|
||||
trie_count_intersect/3,
|
||||
trie_dup/2,
|
||||
trie_save/2,
|
||||
trie_load/2,
|
||||
trie_stats/4,
|
||||
trie_max_stats/4,
|
||||
trie_usage/4,
|
||||
trie_print/1,
|
||||
open_trie/1,
|
||||
close_trie/1,
|
||||
close_all_tries/0,
|
||||
put_trie_entry/4,
|
||||
get_trie_entry/3,
|
||||
remove_trie_entry/1,
|
||||
print_trie/1,
|
||||
trie_traverse_mode/1,
|
||||
trie_disable_hash/0,
|
||||
trie_enable_hash/0,
|
||||
trie_traverse_first/2,
|
||||
trie_traverse_next/2,
|
||||
trie_to_list/2,
|
||||
trie_to_depth_breadth_trie/4,
|
||||
trie_to_depth_breadth_trie/6,
|
||||
trie_get_depth_breadth_reduction_entry/1,
|
||||
trie_get_depth_breadth_reduction_opt_level_count/2,
|
||||
trie_replace_nested_trie/3
|
||||
]).
|
||||
|
||||
/** @defgroup Tries Trie DataStructure
|
||||
/** @defgroup tries Trie DataStructure
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -147,51 +200,6 @@ number of _VirtualNodes_.
|
||||
|
||||
|
||||
*/
|
||||
:- module(tries, [
|
||||
trie_open/1,
|
||||
trie_close/1,
|
||||
trie_close_all/0,
|
||||
trie_empty/1,
|
||||
trie_mode/1,
|
||||
trie_put_entry/3,
|
||||
trie_check_entry/3,
|
||||
trie_get_entry/2,
|
||||
trie_get_first_entry/2,
|
||||
trie_get_last_entry/2,
|
||||
trie_traverse/2,
|
||||
trie_traverse/3,
|
||||
trie_remove_entry/1,
|
||||
trie_remove_subtree/1,
|
||||
trie_join/2,
|
||||
trie_intersect/2,
|
||||
trie_count_join/3,
|
||||
trie_count_intersect/3,
|
||||
trie_dup/2,
|
||||
trie_save/2,
|
||||
trie_load/2,
|
||||
trie_stats/4,
|
||||
trie_max_stats/4,
|
||||
trie_usage/4,
|
||||
trie_print/1,
|
||||
open_trie/1,
|
||||
close_trie/1,
|
||||
close_all_tries/0,
|
||||
put_trie_entry/4,
|
||||
get_trie_entry/3,
|
||||
remove_trie_entry/1,
|
||||
print_trie/1,
|
||||
trie_traverse_mode/1,
|
||||
trie_disable_hash/0,
|
||||
trie_enable_hash/0,
|
||||
trie_traverse_first/2,
|
||||
trie_traverse_next/2,
|
||||
trie_to_list/2,
|
||||
trie_to_depth_breadth_trie/4,
|
||||
trie_to_depth_breadth_trie/6,
|
||||
trie_get_depth_breadth_reduction_entry/1,
|
||||
trie_get_depth_breadth_reduction_opt_level_count/2,
|
||||
trie_replace_nested_trie/3
|
||||
]).
|
||||
|
||||
:- load_foreign_files([tries], [], init_tries).
|
||||
|
||||
|
@@ -1,15 +1,46 @@
|
||||
/**
|
||||
* @file ugraphs.yap
|
||||
* @author R.A.O'Keefe
|
||||
* @author adapted to support some of the functionality of the SICStus ugraphs library
|
||||
by Vitor Santos Costa.
|
||||
* @date 20 March 1984
|
||||
*
|
||||
* @brief
|
||||
*
|
||||
*
|
||||
*/
|
||||
% File : GRAPHS.PL
|
||||
% Author : R.A.O'Keefe
|
||||
% Updated: 20 March 1984
|
||||
% Purpose: Graph-processing utilities.
|
||||
% Updated:
|
||||
% Purpose: .
|
||||
|
||||
%
|
||||
% adapted to support some of the functionality of the SICStus ugraphs library
|
||||
% by Vitor Santos Costa.
|
||||
%
|
||||
%
|
||||
|
||||
|
||||
/** @defgroup UGraphs Unweighted Graphs
|
||||
:- module(ugraphs,
|
||||
[
|
||||
add_vertices/3,
|
||||
add_edges/3,
|
||||
complement/2,
|
||||
compose/3,
|
||||
del_edges/3,
|
||||
del_vertices/3,
|
||||
edges/2,
|
||||
neighbours/3,
|
||||
neighbors/3,
|
||||
reachable/3,
|
||||
top_sort/2,
|
||||
top_sort/3,
|
||||
transitive_closure/2,
|
||||
transpose/2,
|
||||
vertices/2,
|
||||
vertices_edges_to_ugraph/3,
|
||||
ugraph_union/3
|
||||
]).
|
||||
|
||||
|
||||
/** @defgroup ugraphs Unweighted Graphs
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
@@ -293,26 +324,6 @@ L = [1,2,3,4,5]
|
||||
|
||||
|
||||
*/
|
||||
:- module(ugraphs,
|
||||
[
|
||||
add_vertices/3,
|
||||
add_edges/3,
|
||||
complement/2,
|
||||
compose/3,
|
||||
del_edges/3,
|
||||
del_vertices/3,
|
||||
edges/2,
|
||||
neighbours/3,
|
||||
neighbors/3,
|
||||
reachable/3,
|
||||
top_sort/2,
|
||||
top_sort/3,
|
||||
transitive_closure/2,
|
||||
transpose/2,
|
||||
vertices/2,
|
||||
vertices_edges_to_ugraph/3,
|
||||
ugraph_union/3
|
||||
]).
|
||||
|
||||
:- use_module(library(lists), [
|
||||
append/3,
|
||||
|
@@ -1,8 +1,16 @@
|
||||
/**
|
||||
* @file undgraphs.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date 2006
|
||||
*
|
||||
* @brief Directed Graph Processing Utilities.
|
||||
*
|
||||
*
|
||||
*/
|
||||
% File : dgraphs.yap
|
||||
% Author : Vitor Santos Costa
|
||||
% Updated: 2006
|
||||
% Purpose: Directed Graph Processing Utilities.
|
||||
|
||||
% Purpose:
|
||||
|
||||
:- module( undgraphs,
|
||||
[
|
||||
@@ -19,7 +27,7 @@
|
||||
undgraph_components/2,
|
||||
undgraph_min_tree/2]).
|
||||
|
||||
/** @defgroup UnDGraphs Undirected Graphs
|
||||
/** @defgroup undgraphs Undirected Graphs
|
||||
@ingroup library
|
||||
@{
|
||||
|
||||
|
@@ -1,7 +1,12 @@
|
||||
% File : varnumbers.yap
|
||||
% Author : Vitor Santos Costa
|
||||
% Updated: 2006
|
||||
% Purpose: opposite to numbervars
|
||||
/**
|
||||
* @file varnumbers.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date 2006
|
||||
*
|
||||
* @brief opposite to numbervars
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module(varnumbers, [
|
||||
numbervars/1,
|
||||
@@ -9,6 +14,12 @@
|
||||
varnumbers/2
|
||||
]).
|
||||
|
||||
/**
|
||||
* @defgroup varnumbers Variabilize term.
|
||||
* @ingroup ellllllllllllllllllllllllllllllllllllllllllllllllllllllllllllllll
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
numbervars(Term) :-
|
||||
numbervars(Term, 0, _).
|
||||
|
@@ -1,7 +1,12 @@
|
||||
% File : wdgraphs.yap
|
||||
% Author : Vitor Santos Costa
|
||||
% Updated: 2006
|
||||
% Purpose: Weighted Directed Graph Processing Utilities.
|
||||
/**
|
||||
* @file wdgraphs.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date 2006
|
||||
*
|
||||
* @brief Weighted Directed Graph Processing Utilities.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
:- module( wdgraphs,
|
||||
[
|
||||
@@ -30,6 +35,74 @@
|
||||
wdgraph_path/3,
|
||||
wdgraph_reachable/3]).
|
||||
|
||||
/Weighted Directed Graph Processing Utilities.
|
||||
|
||||
:- module( wdgraphs,
|
||||
[
|
||||
wdgraph_new/1,
|
||||
wdgraph_add_edge/5,
|
||||
wdgraph_add_edges/3,
|
||||
wdgraph_add_vertices_and_edges/4,
|
||||
wdgraph_del_edge/5,
|
||||
wdgraph_del_edges/3,
|
||||
wdgraph_del_vertex/3,
|
||||
wdgraph_del_vertices/3,
|
||||
wdgraph_edge/4,
|
||||
wdgraph_to_dgraph/2,
|
||||
dgraph_to_wdgraph/2,
|
||||
wdgraph_neighbors/3,
|
||||
wdgraph_neighbours/3,
|
||||
wdgraph_wneighbors/3,
|
||||
wdgraph_wneighbours/3,
|
||||
wdgraph_transpose/2,
|
||||
wdgraph_transitive_closure/2,
|
||||
wdgraph_symmetric_closure/2,
|
||||
wdgraph_top_sort/2,
|
||||
wdgraph_min_path/5,
|
||||
wdgraph_min_paths/3,
|
||||
wdgraph_max_path/5,
|
||||
wdgraph_path/3,
|
||||
wdgraph_reachable/3]).
|
||||
|
||||
/**
|
||||
* @defgroup wdgraphs Weighted Directed Graph Processing Utilities.
|
||||
|
||||
:- module( wdgraphs,
|
||||
[
|
||||
wdgraph_new/1,
|
||||
wdgraph_add_edge/5,
|
||||
wdgraph_add_edges/3,
|
||||
wdgraph_add_vertices_and_edges/4,
|
||||
wdgraph_del_edge/5,
|
||||
wdgraph_del_edges/3,
|
||||
wdgraph_del_vertex/3,
|
||||
wdgraph_del_vertices/3,
|
||||
wdgraph_edge/4,
|
||||
wdgraph_to_dgraph/2,
|
||||
dgraph_to_wdgraph/2,
|
||||
wdgraph_neighbors/3,
|
||||
wdgraph_neighbours/3,
|
||||
wdgraph_wneighbors/3,
|
||||
wdgraph_wneighbours/3,
|
||||
wdgraph_transpose/2,
|
||||
wdgraph_transitive_closure/2,
|
||||
wdgraph_symmetric_closure/2,
|
||||
wdgraph_top_sort/2,
|
||||
wdgraph_min_path/5,
|
||||
wdgraph_min_paths/3,
|
||||
wdgraph_max_path/5,
|
||||
wdgraph_path/3,
|
||||
wdgraph_reachable/3]).
|
||||
|
||||
/**
|
||||
* @defgroup wdgraphs
|
||||
/**
|
||||
* @defgroup wdgraphs Weighted Directed Graph Processing Utilities.
|
||||
* @ingroup library
|
||||
*
|
||||
*/
|
||||
|
||||
|
||||
:- reexport(library(dgraphs),
|
||||
[dgraph_add_vertex/3 as wdgraph_add_vertex,
|
||||
dgraph_add_vertices/3 as wdgraph_add_vertices,
|
||||
|
@@ -1,3 +1,13 @@
|
||||
/**
|
||||
* @file wgraphs.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date 2006
|
||||
*
|
||||
* @brief Weighted Graph Processing Utilities.
|
||||
*
|
||||
*
|
||||
*/
|
||||
|
||||
/**************************************
|
||||
|
||||
SICStus compatible wgraphs.yap
|
||||
@@ -8,6 +18,12 @@ SICStus compatible wgraphs.yap
|
||||
[vertices_edges_to_wgraph/3]
|
||||
).
|
||||
|
||||
/**
|
||||
* @defgroup wgraphs
|
||||
* @ingroup library
|
||||
*/
|
||||
|
||||
|
||||
:- reexport(library(wdgraphs),
|
||||
[wdgraph_vertices/2 as vertices,
|
||||
wdgraph_edges/2 as edges,
|
||||
|
@@ -1,7 +1,10 @@
|
||||
% File : dgraphs.yap
|
||||
% Author : Vitor Santos Costa
|
||||
% Updated: 2006
|
||||
% Purpose: Directed Graph Processing Utilities.
|
||||
/**
|
||||
* @file wundgraphs.yap
|
||||
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
|
||||
* @date 2006
|
||||
*
|
||||
* @brief Directed Graph Processing Utilities.
|
||||
*/
|
||||
|
||||
:- module( wundgraphs,
|
||||
[
|
||||
@@ -18,6 +21,12 @@
|
||||
wundgraph_min_tree/3,
|
||||
wundgraph_max_tree/3]).
|
||||
|
||||
/**
|
||||
* @defgroup wundgraphs
|
||||
* @ingroup library
|
||||
*/
|
||||
|
||||
|
||||
:- reexport( library(wdgraphs),
|
||||
[
|
||||
wdgraph_new/1 as wundgraph_new,
|
||||
|
@@ -1,9 +1,18 @@
|
||||
/**
|
||||
* @file ypp.yap
|
||||
* @author Nuno Fonseca (nunofonseca@acm.org), Tiago Soares
|
||||
* @date 2005-05-14
|
||||
*
|
||||
* @brief Yap PreProcessing
|
||||
*
|
||||
*
|
||||
*/
|
||||
%====================================================================================
|
||||
%
|
||||
% YPP: Yap PreProcessing
|
||||
%
|
||||
% Author: Nuno Fonseca (nunofonseca@acm.org)
|
||||
% Date: 2005-05-14
|
||||
% Date:
|
||||
% $Id: ypp.yap,v 1.4 2006-03-07 17:30:47 tiagosoares Exp $
|
||||
%
|
||||
%====================================================================================
|
||||
@@ -20,7 +29,14 @@
|
||||
ypp_consult/1, % similiar to standard consult but with preprocessing
|
||||
ypp_reconsult/1
|
||||
]
|
||||
).
|
||||
).
|
||||
|
||||
/**
|
||||
* @defgroup ypp Yap PreProcessing
|
||||
* @ingroup library
|
||||
*
|
||||
*/
|
||||
|
||||
%====================================================================================
|
||||
% Public Predicates
|
||||
%====================================================================================
|
||||
|
Reference in New Issue
Block a user