This commit is contained in:
Vitor Santos Costa
2018-05-01 23:25:58 +01:00
parent 44ac70d3ab
commit ef04b30d66
56 changed files with 2229 additions and 2422 deletions

View File

@@ -11,30 +11,6 @@
:- 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.
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
*/
:- reexport(library(maplist),
[maplist/2,
@@ -47,6 +23,31 @@ The apply library is a _stub_, it just forwards definitions to the
partition/5
]).
/**
* @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.
The apply library is a _stub_, it just forwards definitions to the
@ref maplist library. The predicates forwarded are:
- @ref maplist/2,
- @ref maplist/3,
- @ref maplist/4,
- @ref maplist/5,
- @ref include/3,
- @ref exclude/3,
- @ref partition/4,
- @ref partition/5
*/
%% @}

View File

@@ -2,8 +2,8 @@
%% @file apply_macros.yap
%% @author E. Alphonse from code by Joachim Schimpf
%% @date 15 June 2002
%% @nrief Purpose: Macros to apply a predicate to all elements
% of a list or to all sub-terms of a term.
%% @brief Purpose: Macros to apply a predicate to all elements
%% of a list or to all sub-terms of a term.
:- module(apply_macros, []).

View File

@@ -2,15 +2,8 @@
* @file library/lists.yap
* @author Bob Welham, Lawrence Byrd, and R. A. O'Keefe. Contributions from Vitor Santos Costa, Jan Wielemaker and others.
* @date 1999
*
* @{
*
x * @addtogroup library The Prolog Library
*
* @brief List Manipulation Predicates
*
*
*/
% This file has been included as an YAP library by Vitor Santos Costa, 1999
:- module(lists,
@@ -52,15 +45,18 @@ x * @addtogroup library The Prolog Library
]).
/** @defgroup lists List Manipulation
@ingroup library
@{
The following list manipulation routines are available once included
with the `use_module(library(lists))` command.
/**
* @{
*
* @addtogroup library The Prolog Library
*
* @brief List Manipulation Predicates
*
* The following list manipulation routines are available once included
with the `use_module(library(lists))` command.
*/
/** @pred list_concat(+ _Lists_,? _List_)

View File

@@ -47,6 +47,7 @@
/**
* @defgroup maplist Map List and Term Operations
* @ingroup library
* @{
*
* This library provides a set of utilities for applying a predicate to
* all elements of a list. They allow one to easily perform the most common do-loop constructs in Prolog.
@@ -56,20 +57,20 @@
* by Joachim Schimpf and on code from SWI-Prolog, and it is also inspired by the GHC
* libraries.
*
* The following routines are available once included with the
* The routines are available once included with the
* `use_module(library(apply_macros))` command.
* @author : Lawrence Byrd
* @author Richard A. O'Keefe
* @author Joachim Schimpf
* @author Jan Wielemaker
* @author E. Alphonse
* @author Vitor Santos Costa
*/
/*
Examples:
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~{.prolog}
%given
~~~~
given the progran:
~~~~
plus(X,Y,Z) :- Z is X + Y.
plus_if_pos(X,Y,Z) :- Y > 0, Z is X + Y.
@@ -82,7 +83,7 @@ trans(TermIn, TermOut) :-
TermIn =.. [p|Args],
TermOut =..[q|Args], !.
trans(X,X).
~~~~
%success
?- maplist(plus(1), [1,2,3,4], [2,3,4,5]).
@@ -96,15 +97,13 @@ trans(X,X).
?- sumlist(plus, [1,2,3,4], 1, 11).
?- maplist(mapargs(number_atom),[c(1),s(1,2,3)],[c('1'),s('1','2','3')]).
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
@{
~~~~
*/
/** @pred maplist(+ _Pred_,+ _List1_,+ _List2_)
/** @pred maplist( 2:Pred, + _List1_,+ _List2_)
Apply _Pred_ on all successive pairs of elements from
_List1_ and
@@ -113,7 +112,8 @@ pair. See the example above.
*/
/** @pred maplist(+ _Pred_,+ _List1_,+ _List2_,+ _List4_)
/** @pred maplist(3:Pred,+ List1,+ List2,+ List4)
Apply _Pred_ on all successive triples of elements from _List1_,
_List2_ and _List3_. Fails if _Pred_ can not be applied to a
@@ -167,13 +167,17 @@ triple. See the example above.
%
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
/** include(+ _Pred_, + _ListIn_, ? _ListOut_)
/**
@pred include( 2:Pred, + ListIn, ? ListOut)
Same as selectlist/3.
*/
include(G,In,Out) :-
selectlist(G, In, Out).
/** selectlist(: _Pred_, + _ListIn_, ? _ListOut_))
/**
@pred selectlist(1:Pred, + ListIn, ? ListOut))
Creates _ListOut_ of all list elements of _ListIn_ that pass a given test
*/
selectlist(_, [], []).
@@ -185,7 +189,9 @@ selectlist(Pred, [In|ListIn], ListOut) :-
),
selectlist(Pred, ListIn, NewListOut).
/** selectlist(: _Pred_, + _ListIn_, + _ListInAux_, ? _ListOut_, ? _ListOutAux_)
/**
@pred selectlist( 2:Pred, + ListIn, + ListInAux, ? ListOut, ? ListOutAux)
Creates _ListOut_ and _ListOutAux_ of all list elements of _ListIn_ and _ListInAux_ that
pass the given test _Pred_.
*/
@@ -200,7 +206,8 @@ selectlists(Pred, [In|ListIn], [In1|ListIn1], ListOut, ListOut1) :-
),
selectlist(Pred, ListIn, ListIn1, NewListOut, NewListOut1).
/** selectlist(: _Pred_, + _ListIn_, + _ListInAux_, ? _ListOut_)
/** @pred selectlist( 2:Pred, + ListIn, + ListInAux, ? ListOut)
Creates _ListOut_ of all list elements of _ListIn_ that
pass the given test _Pred_ using + _ListInAux_ as an
auxiliary element.
@@ -214,7 +221,9 @@ selectlist(Pred, [In|ListIn], [In1|ListIn1], ListOut) :-
),
selectlist(Pred, ListIn, ListIn1, NewListOut).
/** exclude(+ _Goal_, + _List1_, ? _List2_)
/**
@pred exclude( 2:Goal, + List1, ? List2)
Filter elements for which _Goal_ fails. True if _List2_ contains
those elements _Xi_ of _List1_ for which `call(Goal, Xi)` fails.
*/
@@ -227,11 +236,13 @@ exclude(Pred, [In|ListIn], ListOut) :-
),
exclude(Pred, ListIn, NewListOut).
/** partition(+ _Pred_, + _List1_, ? _Included_, ? _Excluded_)
Filter elements of _List_ according to _Pred_. True if
/**
@pred partition(1:Pred, + List1, ? Included, ? Excluded)
Filter elements of _List1_ according to _Pred_. True if
_Included_ contains all elements for which `call(Pred, X)`
succeeds and _Excluded_ contains the remaining elements.
*/
*/
partition(_, [], [], []).
partition(Pred, [In|ListIn], List1, List2) :-
(call(Pred, In) ->
@@ -243,7 +254,8 @@ partition(Pred, [In|ListIn], List1, List2) :-
),
partition(Pred, ListIn, RList1, RList2).
/** partition(+ _Pred_, + _List1_, ? _Lesser_, ? _Equal_, ? _Greater_)
/**
@pred partition(2:Pred, + List1, ? Lesser, ? Equal, ? Greater)
Filter list according to _Pred_ in three sets. For each element
_Xi_ of _List_, its destination is determined by
@@ -274,7 +286,9 @@ partition(Pred, [In|ListIn], List1, List2, List3) :-
),
partition(Pred, ListIn, RList1, RList2, RList3).
/** checklist(: _Pred_, + _List_)
/**
@pred checklist( 1:Pred, + List)
Succeeds if the predicate _Pred_ succeeds on all elements of _List_.
*/
checklist(_, []).
@@ -282,7 +296,8 @@ checklist(Pred, [In|ListIn]) :-
call(Pred, In),
checklist(Pred, ListIn).
/** maplist(: _Pred_, ? _ListIn_)
/**
@pred maplist(: Pred, ? ListIn)
Applies predicate _Pred_( _El_ ) to all
elements _El_ of _ListIn_.
@@ -294,7 +309,8 @@ maplist(Pred, [In|ListIn]) :-
maplist(Pred, ListIn).
/** maplist(: _Pred_, ? _L1_, ? _L2_ )
/**
@pred maplist(: Pred, ? L1, ? L2 )
_L1_ and _L2_ are such that
`call( _Pred_, _A1_, _A2_)` holds for every
corresponding element in lists _L1_, _L2_.
@@ -308,7 +324,8 @@ maplist(Pred, [In|ListIn], [Out|ListOut]) :-
call(Pred, In, Out),
maplist(Pred, ListIn, ListOut).
/** maplist(: _Pred_, ? _L1_, ? _L2_, ? _L3_)
/**
@pred maplist(: Pred, ? L1, ? L2, ? L3)
_L1_, _L2_, and _L3_ are such that
`call( _Pred_, _A1_, _A2_, _A3_)` holds for every
corresponding element in lists _L1_, _L2_, and _L3_.
@@ -319,7 +336,9 @@ maplist(Pred, [A1|L1], [A2|L2], [A3|L3]) :-
call(Pred, A1, A2, A3),
maplist(Pred, L1, L2, L3).
/** maplist(: _Pred_, ? _L1_, ? _L2_, ? _L3_, ? _L4_)
/**
@pred maplist(: Pred, ? L1, ? L2, ? L3, ? L4)
_L1_, _L2_, _L3_, and _L4_ are such that
`call( _Pred_, _A1_, _A2_, _A3_, _A4_)` holds
for every corresponding element in lists _L1_, _L2_, _L3_, and
@@ -331,7 +350,7 @@ maplist(Pred, [A1|L1], [A2|L2], [A3|L3], [A4|L4]) :-
maplist(Pred, L1, L2, L3, L4).
/**
convlist(: _Pred_, + _ListIn_, ? _ListOut_) @anchor convlist3
@pred convlist(: Pred, + ListIn, ? ListOut)
A combination of maplist/3 and selectlist/3: creates _ListOut_ by
applying the predicate _Pred_ to all list elements on which
@@ -355,7 +374,7 @@ convlist(Pred, [_|Olds], News) :-
convlist(Pred, Olds, News).
/**
convlist(: Pred, ? ListIn, ?ExtraList, ? ListOut) @anchor convlist5
@pred convlist(: Pred, ? ListIn, ?ExtraList, ? ListOut)
A combination of maplist/4 and selectlist/3: _ListIn_, _ListExtra_,
and _ListOut_ are the sublists so that the predicate _Pred_ succeeds.
@@ -378,7 +397,7 @@ convlist(Pred, [_|Olds], News) :-
convlist(Pred, Olds, News).
/**
mapnodes(+ _Pred_, + _TermIn_, ? _TermOut_)
@pred mapnodes(+ _Pred_, + _TermIn_, ? _TermOut_)
Creates _TermOut_ by applying the predicate _Pred_
to all sub-terms of _TermIn_ (depth-first and left-to-right order).
@@ -398,7 +417,7 @@ mapnodes_list(Pred, [TermIn|ArgsIn], [TermOut|ArgsOut]) :-
mapnodes_list(Pred, ArgsIn, ArgsOut).
/**
checknodes(+ _Pred_, + _Term_) @anchor checknodes
@pred checknodes(+ _Pred_, + _Term_)
Succeeds if the predicate _Pred_ succeeds on all sub-terms of
_Term_ (depth-first and left-to-right order)
@@ -416,8 +435,8 @@ checknodes_list(Pred, [Term|Args]) :-
checknodes_body(Pred, Term),
checknodes_list(Pred, Args).
/**
sumlist(: _Pred_, + _List_, ? _AccIn_, ? _AccOut_)
/**
@pred sumlist(: _Pred_, + _List_, ? _AccIn_, ? _AccOut_)
Calls _Pred_ on all elements of List and collects a result in
_Accumulator_. Same as fold/4.
@@ -428,7 +447,7 @@ sumlist(Pred, [H|T], AccIn, AccOut) :-
sumlist(Pred, T, A1, AccOut).
/**
sumnodes(+ _Pred_, + _Term_, ? _AccIn_, ? _AccOut_) @anchor sumnodes
@pred sumnodes(+ _Pred_, + _Term_, ? _AccIn_, ? _AccOut_)
Calls the predicate _Pred_ on all sub-terms of _Term_ and
collect a result in _Accumulator_ (depth-first and left-to-right
@@ -457,11 +476,12 @@ sumnodes_body(Pred, Term, A1, A3, N0, Ar) :-
* FOLDL *
*******************************/
%% foldl(:Goal, +List, +V0, -V, +W0, -WN).
%%
%% @pred foldl(:Goal, +List, +V0, -V, +W0, -WN).
%
/**
foldl(: _Pred_, + _List1_, + _List2_, ? _AccIn_, ? _AccOut_)
@pred oldl(: _Pred_, + _List1_, + _List2_, ? _AccIn_, ? _AccOut_)
Calls _Pred_ on all elements of `List1` and collects a result in _Accumulator_. Same as
foldr/3.
@@ -475,7 +495,7 @@ foldl_([H|T], Goal, V0, V) :-
foldl_(T, Goal, V1, V).
/**
foldl(: _Pred_, + _List1_, + _List2_, ? _AccIn_, ? _AccOut_)
@pred foldl(: _Pred_, + _List1_, + _List2_, ? _AccIn_, ? _AccOut_)
Calls _Pred_ on all elements of _List1_ and
_List2_ and collects a result in _Accumulator_. Same as
@@ -522,7 +542,7 @@ foldl_([H1|T1], [H2|T2], [H3|T3], [H4|T4], Goal, V0, V) :-
/**
foldl2(: _Pred_, + _List_, ? _X0_, ? _X_, ? _Y0_, ? _Y_)
@pred foldl2(: _Pred_, + _List_, ? _X0_, ? _X_, ? _Y0_, ? _Y_)
Calls _Pred_ on all elements of `List` and collects a result in
_X_ and _Y_.
@@ -537,7 +557,7 @@ foldl2_([H|T], Goal, V0, V, W0, W) :-
foldl2_(T, Goal, V1, V, W1, W).
/**
foldl2(: _Pred_, + _List_, ? _List1_, ? _X0_, ? _X_, ? _Y0_, ? _Y_)
v @pred foldl2(: _Pred_, + _List_, ? _List1_, ? _X0_, ? _X_, ? _Y0_, ? _Y_)
Calls _Pred_ on all elements of _List_ and _List1_ and collects a result in
_X_ and _Y_.
@@ -551,7 +571,7 @@ foldl2_([H1|T1], [H2|T2], Goal, V0, V, W0, W) :-
foldl2_(T1, T2, Goal, V1, V, W1, W).
/**
foldl2(: _Pred_, + _List_, ? _List1_, ? _List2_, ? _X0_, ? _X_, ? _Y0_, ? _Y_)
@pred foldl2(: _Pred_, + _List_, ? _List1_, ? _List2_, ? _X0_, ? _X_, ? _Y0_, ? _Y_)
Calls _Pred_ on all elements of _List_, _List1_ and _List2_ and collects a result in
_X_ and _Y_.
@@ -567,7 +587,7 @@ foldl2_([H1|T1], [H2|T2], [H3|T3], Goal, V0, V, W0, W) :-
/**
foldl3(: _Pred_, + _List1_, ? _List2_, ? _X0_, ? _X_, ? _Y0_, ? _Y_, ? _Z0_, ? _Z_)
@pred foldl3(: _Pred_, + _List1_, ? _List2_, ? _X0_, ? _X_, ? _Y0_, ? _Y_, ? _Z0_, ? _Z_)
Calls _Pred_ on all elements of `List` and collects a
@@ -582,7 +602,7 @@ foldl3_([H|T], Goal, V0, V, W0, W, X0, X) :-
fold3_(T, Goal, V1, V, W1, W, X1, X).
/**
foldl4(: _Pred_, + _List1_, ? _List2_, ? _X0_, ? _X_, ? _Y0_, ? _Y_, ? _Z0_, ? _Z_, ? _W0_, ? _W_)
@pred foldl4(: _Pred_, + _List1_, ? _List2_, ? _X0_, ? _X_, ? _Y0_, ? _Y_, ? _Z0_, ? _Z_, ? _W0_, ? _W_)
Calls _Pred_ on all elements of `List` and collects a
@@ -618,7 +638,6 @@ foldl4_([H|T], Goal, V0, V, W0, W, X0, X, Y0, Y) :-
% ==
/**
scanl(: _Pred_, + _List_, + _V0_, ? _Values_)
Left scan of list. The scanl family of higher order list

View File

@@ -37,26 +37,46 @@
* @(#)cclass.h 8.3 (Berkeley) 3/20/94
*/
/**
* @file cclass.h
*
* @brief Regexp character classes.
*
* @namespace regexp
*
*/
typedef enum {CALNUM, CALPHA, CBLANK, CCNTRL, CDIGIT, CGRAPH,
CLOWER, CPRINT, CPUNCT, CSPACE, CUPPER, CXDIGIT} citype;
typedef enum {
CALNUM,
CALPHA,
CBLANK,
CCNTRL,
CDIGIT,
CGRAPH,
CLOWER,
CPRINT,
CPUNCT,
CSPACE,
CUPPER,
CXDIGIT
} citype;
/* character-class table */
static struct cclass {
char *name;
citype fidx;
} cclasses[] = {
{"alnum", CALNUM},
{"alpha", CALPHA},
{"blank", CBLANK},
{"cntrl", CCNTRL},
{"digit", CDIGIT},
{"graph", CGRAPH},
{"lower", CLOWER},
{"print", CPRINT},
{"punct", CPUNCT},
{"space", CSPACE},
{"upper", CUPPER},
{"xdigit", CXDIGIT},
{NULL, }
};
char *name;
citype fidx;
} cclasses[] = {{"alnum", CALNUM},
{"alpha", CALPHA},
{"blank", CBLANK},
{"cntrl", CCNTRL},
{"digit", CDIGIT},
{"graph", CGRAPH},
{"lower", CLOWER},
{"print", CPRINT},
{"punct", CPUNCT},
{"space", CSPACE},
{"upper", CUPPER},
{"xdigit", CXDIGIT},
{
NULL,
}};

View File

@@ -37,105 +37,112 @@
* @(#)cname.h 8.3 (Berkeley) 3/20/94
*/
/**
* @file cname.h
*
* Vharacter names.
*
* @namespace regexp
*
*/
/* character-name table */
static struct cname {
char *name;
char code;
} cnames[] = {
{"NUL", '\0'},
{"SOH", '\001'},
{"STX", '\002'},
{"ETX", '\003'},
{"EOT", '\004'},
{"ENQ", '\005'},
{"ACK", '\006'},
{"BEL", '\007'},
{"alert", '\007'},
{"BS", '\010'},
{"backspace", '\b'},
{"HT", '\011'},
{"tab", '\t'},
{"LF", '\012'},
{"newline", '\n'},
{"VT", '\013'},
{"vertical-tab", '\v'},
{"FF", '\014'},
{"form-feed", '\f'},
{"CR", '\015'},
{"carriage-return", '\r'},
{"SO", '\016'},
{"SI", '\017'},
{"DLE", '\020'},
{"DC1", '\021'},
{"DC2", '\022'},
{"DC3", '\023'},
{"DC4", '\024'},
{"NAK", '\025'},
{"SYN", '\026'},
{"ETB", '\027'},
{"CAN", '\030'},
{"EM", '\031'},
{"SUB", '\032'},
{"ESC", '\033'},
{"IS4", '\034'},
{"FS", '\034'},
{"IS3", '\035'},
{"GS", '\035'},
{"IS2", '\036'},
{"RS", '\036'},
{"IS1", '\037'},
{"US", '\037'},
{"space", ' '},
{"exclamation-mark", '!'},
{"quotation-mark", '"'},
{"number-sign", '#'},
{"dollar-sign", '$'},
{"percent-sign", '%'},
{"ampersand", '&'},
{"apostrophe", '\''},
{"left-parenthesis", '('},
{"right-parenthesis", ')'},
{"asterisk", '*'},
{"plus-sign", '+'},
{"comma", ','},
{"hyphen", '-'},
{"hyphen-minus", '-'},
{"period", '.'},
{"full-stop", '.'},
{"slash", '/'},
{"solidus", '/'},
{"zero", '0'},
{"one", '1'},
{"two", '2'},
{"three", '3'},
{"four", '4'},
{"five", '5'},
{"six", '6'},
{"seven", '7'},
{"eight", '8'},
{"nine", '9'},
{"colon", ':'},
{"semicolon", ';'},
{"less-than-sign", '<'},
{"equals-sign", '='},
{"greater-than-sign", '>'},
{"question-mark", '?'},
{"commercial-at", '@'},
{"left-square-bracket", '['},
{"backslash", '\\'},
{"reverse-solidus", '\\'},
{"right-square-bracket",']'},
{"circumflex", '^'},
{"circumflex-accent", '^'},
{"underscore", '_'},
{"low-line", '_'},
{"grave-accent", '`'},
{"left-brace", '{'},
{"left-curly-bracket", '{'},
{"vertical-line", '|'},
{"right-brace", '}'},
{"right-curly-bracket", '}'},
{"tilde", '~'},
{"DEL", '\177'},
{NULL, 0}
};
char *name;
char code;
} cnames[] = {{"NUL", '\0'},
{"SOH", '\001'},
{"STX", '\002'},
{"ETX", '\003'},
{"EOT", '\004'},
{"ENQ", '\005'},
{"ACK", '\006'},
{"BEL", '\007'},
{"alert", '\007'},
{"BS", '\010'},
{"backspace", '\b'},
{"HT", '\011'},
{"tab", '\t'},
{"LF", '\012'},
{"newline", '\n'},
{"VT", '\013'},
{"vertical-tab", '\v'},
{"FF", '\014'},
{"form-feed", '\f'},
{"CR", '\015'},
{"carriage-return", '\r'},
{"SO", '\016'},
{"SI", '\017'},
{"DLE", '\020'},
{"DC1", '\021'},
{"DC2", '\022'},
{"DC3", '\023'},
{"DC4", '\024'},
{"NAK", '\025'},
{"SYN", '\026'},
{"ETB", '\027'},
{"CAN", '\030'},
{"EM", '\031'},
{"SUB", '\032'},
{"ESC", '\033'},
{"IS4", '\034'},
{"FS", '\034'},
{"IS3", '\035'},
{"GS", '\035'},
{"IS2", '\036'},
{"RS", '\036'},
{"IS1", '\037'},
{"US", '\037'},
{"space", ' '},
{"exclamation-mark", '!'},
{"quotation-mark", '"'},
{"number-sign", '#'},
{"dollar-sign", '$'},
{"percent-sign", '%'},
{"ampersand", '&'},
{"apostrophe", '\''},
{"left-parenthesis", '('},
{"right-parenthesis", ')'},
{"asterisk", '*'},
{"plus-sign", '+'},
{"comma", ','},
{"hyphen", '-'},
{"hyphen-minus", '-'},
{"period", '.'},
{"full-stop", '.'},
{"slash", '/'},
{"solidus", '/'},
{"zero", '0'},
{"one", '1'},
{"two", '2'},
{"three", '3'},
{"four", '4'},
{"five", '5'},
{"six", '6'},
{"seven", '7'},
{"eight", '8'},
{"nine", '9'},
{"colon", ':'},
{"semicolon", ';'},
{"less-than-sign", '<'},
{"equals-sign", '='},
{"greater-than-sign", '>'},
{"question-mark", '?'},
{"commercial-at", '@'},
{"left-square-bracket", '['},
{"backslash", '\\'},
{"reverse-solidus", '\\'},
{"right-square-bracket", ']'},
{"circumflex", '^'},
{"circumflex-accent", '^'},
{"underscore", '_'},
{"low-line", '_'},
{"grave-accent", '`'},
{"left-brace", '{'},
{"left-curly-bracket", '{'},
{"vertical-line", '|'},
{"right-brace", '}'},
{"right-curly-bracket", '}'},
{"tilde", '~'},
{"DEL", '\177'},
{NULL, 0}};

View File

@@ -44,6 +44,14 @@
* of code.
*/
/**
* @file engine.c
*
* regex interpeter.
*
* @namespace regexp
*/
#include "config.h"
#ifndef HAVE_REGEXEC

File diff suppressed because it is too large Load Diff

View File

@@ -41,13 +41,22 @@
static char sccsid[] = "@(#)regerror.c 8.4 (Berkeley) 3/20/94";
#endif /* LIBC_SCCS and not lint */
#include <sys/types.h>
#include <stdio.h>
#include <string.h>
#include <limits.h>
#include <stdlib.h>
/**
* @file regerror.c
*
* @brief Error handling.
*
* @namespace regexp
*
*/
#include "YapInterface.h"
#include "yapregex.h"
#include <limits.h>
#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <sys/types.h>
#include "utils.h"
@@ -57,7 +66,7 @@ extern "C" {
#endif
/* === regerror.c === */
static char * regatoi(const regex_t *preg, char *localbuf);
static char *regatoi(const regex_t *preg, char *localbuf);
#ifdef __cplusplus
}
@@ -84,91 +93,86 @@ static char * regatoi(const regex_t *preg, char *localbuf);
= #define REG_ITOA 0400 // convert number to name (!)
*/
static struct rerr {
int code;
char *name;
char *explain;
} rerrs[] = {
{REG_NOMATCH, "REG_NOMATCH", "regexec() failed to match"},
{REG_BADPAT, "REG_BADPAT", "invalid regular expression"},
{REG_ECOLLATE, "REG_ECOLLATE", "invalid collating element"},
{REG_ECTYPE, "REG_ECTYPE", "invalid character class"},
{REG_EESCAPE, "REG_EESCAPE", "trailing backslash (\\)"},
{REG_ESUBREG, "REG_ESUBREG", "invalid backreference number"},
{REG_EBRACK, "REG_EBRACK", "brackets ([ ]) not balanced"},
{REG_EPAREN, "REG_EPAREN", "parentheses not balanced"},
{REG_EBRACE, "REG_EBRACE", "braces not balanced"},
{REG_BADBR, "REG_BADBR", "invalid repetition count(s)"},
{REG_ERANGE, "REG_ERANGE", "invalid character range"},
{REG_ESPACE, "REG_ESPACE", "out of memory"},
{REG_BADRPT, "REG_BADRPT", "repetition-operator operand invalid"},
{REG_EMPTY, "REG_EMPTY", "empty (sub)expression"},
{REG_ASSERT, "REG_ASSERT", "\"can't happen\" -- you found a bug"},
{REG_INVARG, "REG_INVARG", "invalid argument to regex routine"},
{0, "", "*** unknown regexp error code ***"}
};
int code;
char *name;
char *explain;
} rerrs[] = {{REG_NOMATCH, "REG_NOMATCH", "regexec() failed to match"},
{REG_BADPAT, "REG_BADPAT", "invalid regular expression"},
{REG_ECOLLATE, "REG_ECOLLATE", "invalid collating element"},
{REG_ECTYPE, "REG_ECTYPE", "invalid character class"},
{REG_EESCAPE, "REG_EESCAPE", "trailing backslash (\\)"},
{REG_ESUBREG, "REG_ESUBREG", "invalid backreference number"},
{REG_EBRACK, "REG_EBRACK", "brackets ([ ]) not balanced"},
{REG_EPAREN, "REG_EPAREN", "parentheses not balanced"},
{REG_EBRACE, "REG_EBRACE", "braces not balanced"},
{REG_BADBR, "REG_BADBR", "invalid repetition count(s)"},
{REG_ERANGE, "REG_ERANGE", "invalid character range"},
{REG_ESPACE, "REG_ESPACE", "out of memory"},
{REG_BADRPT, "REG_BADRPT", "repetition-operator operand invalid"},
{REG_EMPTY, "REG_EMPTY", "empty (sub)expression"},
{REG_ASSERT, "REG_ASSERT", "\"can't happen\" -- you found a bug"},
{REG_INVARG, "REG_INVARG", "invalid argument to regex routine"},
{0, "", "*** unknown regexp error code ***"}};
/*
- regerror - the interface to error numbers
= extern size_t regerror(int, const regex_t *, char *, size_t);
*/
/* ARGSUSED */
size_t
yap_regerror(int errcode,const regex_t *preg,char *errbuf,size_t errbuf_size)
{
register struct rerr *r;
register size_t len;
register int target = errcode &~ REG_ITOA;
register char *s;
char convbuf[50];
size_t yap_regerror(int errcode, const regex_t *preg, char *errbuf,
size_t errbuf_size) {
register struct rerr *r;
register size_t len;
register int target = errcode & ~REG_ITOA;
register char *s;
char convbuf[50];
if (errcode == REG_ATOI)
s = regatoi(preg, convbuf);
else {
for (r = rerrs; r->code != 0; r++)
if (r->code == target)
break;
if (errcode == REG_ATOI)
s = regatoi(preg, convbuf);
else {
for (r = rerrs; r->code != 0; r++)
if (r->code == target)
break;
if (errcode&REG_ITOA) {
if (r->code != 0)
(void) strcpy(convbuf, r->name);
else
sprintf(convbuf, "REG_0x%x", target);
assert(strlen(convbuf) < sizeof(convbuf));
s = convbuf;
} else
s = r->explain;
}
if (errcode & REG_ITOA) {
if (r->code != 0)
(void)strcpy(convbuf, r->name);
else
sprintf(convbuf, "REG_0x%x", target);
assert(strlen(convbuf) < sizeof(convbuf));
s = convbuf;
} else
s = r->explain;
}
len = strlen(s) + 1;
if (errbuf_size > 0) {
if (errbuf_size > len)
(void) strcpy(errbuf, s);
else {
(void) strncpy(errbuf, s, errbuf_size-1);
errbuf[errbuf_size-1] = '\0';
}
}
len = strlen(s) + 1;
if (errbuf_size > 0) {
if (errbuf_size > len)
(void)strcpy(errbuf, s);
else {
(void)strncpy(errbuf, s, errbuf_size - 1);
errbuf[errbuf_size - 1] = '\0';
}
}
return(len);
return (len);
}
/*
- regatoi - internal routine to implement REG_ATOI
== static char *regatoi(const regex_t *preg, char *localbuf);
*/
static char *
regatoi(preg, localbuf)
const regex_t *preg;
static char *regatoi(preg, localbuf) const regex_t *preg;
char *localbuf;
{
register struct rerr *r;
register struct rerr *r;
for (r = rerrs; r->code != 0; r++)
if (strcmp(r->name, preg->re_endp) == 0)
break;
if (r->code == 0)
return("0");
for (r = rerrs; r->code != 0; r++)
if (strcmp(r->name, preg->re_endp) == 0)
break;
if (r->code == 0)
return ("0");
sprintf(localbuf, "%d", r->code);
return(localbuf);
sprintf(localbuf, "%d", r->code);
return (localbuf);
}

View File

@@ -1,19 +1,26 @@
/*************************************************************************
* *
* YAP Prolog *
* *
* Yap Prolog was developed at NCCUP - Universidade do Porto *
* *
* Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997 *
* *
**************************************************************************
* *
* File: regexp.c *
* Last rev: *
* mods: *
* comments: regular expression interpreter *
* *
*************************************************************************/
* *
* YAP Prolog *
* *
* Yap Prolog was developed at NCCUP - Universidade do Porto *
* *
* Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997 *
* *
**************************************************************************
* *
* File: regexp.c * Last rev:
** mods: * comments: regular expression interpreter *
* *
*************************************************************************/
/**
* @file regexp.c
*
* A port of the Unix regular expression compiler.
*
* @namespace regexp
*
*/
#include "config.h"
#if HAVE_SYS_TYPES_H
@@ -22,69 +29,67 @@
#include "YapInterface.h"
#if HAVE_REGEXEC
#include "regex.h"
#define yap_regcomp(A,B,C) regcomp(A,B,C)
#define yap_regexec(A,B,C,D,E) regexec(A,B,C,D,E)
#define yap_regcomp(A, B, C) regcomp(A, B, C)
#define yap_regexec(A, B, C, D, E) regexec(A, B, C, D, E)
#define yap_regfree(A) regfree(A)
#define yap_regerror(A,B,C,D) regfree(A,B,C,D)
#define yap_regerror(A, B, C, D) regfree(A, B, C, D)
#else
#include "yapregex.h"
#endif
/* for the sake of NULL */
#include <stdio.h>
void init_regexp( void );
void init_regexp(void);
static YAP_Bool check_regexp(void)
{
unsigned int buflen = (unsigned int)YAP_IntOfTerm(YAP_ARG2)+1;
unsigned int sbuflen = (unsigned int)YAP_IntOfTerm(YAP_ARG4)+1;
static YAP_Bool check_regexp(void) {
unsigned int buflen = (unsigned int)YAP_IntOfTerm(YAP_ARG2) + 1;
unsigned int sbuflen = (unsigned int)YAP_IntOfTerm(YAP_ARG4) + 1;
char *buf, *sbuf;
regex_t reg;
int out;
int yap_flags = YAP_IntOfTerm(YAP_ARG5);
int regcomp_flags = REG_NOSUB|REG_EXTENDED;
int regcomp_flags = REG_NOSUB | REG_EXTENDED;
if ((buf = (char *)YAP_AllocSpaceFromYap(buflen)) == NULL) {
/* early exit */
return(FALSE);
return (FALSE);
}
if (YAP_StringToBuffer(YAP_ARG1,buf,buflen) == FALSE) {
if (YAP_StringToBuffer(YAP_ARG1, buf, buflen) == FALSE) {
/* something went wrong, possibly a type checking error */
YAP_FreeSpaceFromYap(buf);
return(FALSE);
return (FALSE);
}
if (yap_flags & 1)
regcomp_flags |= REG_ICASE;
/* cool, now I have my string in the buffer, let's have some fun */
if (yap_regcomp(&reg,buf, regcomp_flags) != 0)
return(FALSE);
if (yap_regcomp(&reg, buf, regcomp_flags) != 0)
return (FALSE);
if ((sbuf = (char *)YAP_AllocSpaceFromYap(sbuflen)) == NULL) {
/* early exit */
yap_regfree(&reg);
YAP_FreeSpaceFromYap(buf);
return(FALSE);
return (FALSE);
}
if (YAP_StringToBuffer(YAP_ARG3,sbuf,sbuflen) == FALSE) {
if (YAP_StringToBuffer(YAP_ARG3, sbuf, sbuflen) == FALSE) {
/* something went wrong, possibly a type checking error */
yap_regfree(&reg);
YAP_FreeSpaceFromYap(buf);
YAP_FreeSpaceFromYap(sbuf);
return(FALSE);
YAP_FreeSpaceFromYap(sbuf);
return (FALSE);
}
out = yap_regexec(&reg,sbuf,0,NULL,0);
out = yap_regexec(&reg, sbuf, 0, NULL, 0);
yap_regfree(&reg);
YAP_FreeSpaceFromYap(buf);
YAP_FreeSpaceFromYap(sbuf);
YAP_FreeSpaceFromYap(sbuf);
if (out != 0 && out != REG_NOMATCH) {
return(FALSE);
return (FALSE);
}
return(out == 0);
return (out == 0);
}
static YAP_Bool regexp(void)
{
unsigned int buflen = (unsigned int)YAP_IntOfTerm(YAP_ARG2)+1;
unsigned int sbuflen = (unsigned int)YAP_IntOfTerm(YAP_ARG4)+1;
static YAP_Bool regexp(void) {
unsigned int buflen = (unsigned int)YAP_IntOfTerm(YAP_ARG2) + 1;
unsigned int sbuflen = (unsigned int)YAP_IntOfTerm(YAP_ARG4) + 1;
char *buf, *sbuf;
regex_t reg;
int out;
@@ -93,23 +98,22 @@ static YAP_Bool regexp(void)
long int tout;
int yap_flags = YAP_IntOfTerm(YAP_ARG5);
int regcomp_flags = REG_EXTENDED;
if ((buf = (char *)YAP_AllocSpaceFromYap(buflen)) == NULL) {
/* early exit */
return(FALSE);
return (FALSE);
}
if (YAP_StringToBuffer(YAP_ARG1,buf,buflen) == FALSE) {
if (YAP_StringToBuffer(YAP_ARG1, buf, buflen) == FALSE) {
/* something went wrong, possibly a type checking error */
YAP_FreeSpaceFromYap(buf);
return(FALSE);
return (FALSE);
}
if (yap_flags & 1)
regcomp_flags |= REG_ICASE;
/* cool, now I have my string in the buffer, let's have some fun */
if (yap_regcomp(&reg,buf, regcomp_flags) != 0) {
if (yap_regcomp(&reg, buf, regcomp_flags) != 0) {
YAP_FreeSpaceFromYap(buf);
return(FALSE);
return (FALSE);
}
if (YAP_IsVarTerm(YAP_ARG7)) {
nmatch = reg.re_nsub;
@@ -120,57 +124,54 @@ static YAP_Bool regexp(void)
/* early exit */
yap_regfree(&reg);
YAP_FreeSpaceFromYap(buf);
return(FALSE);
return (FALSE);
}
if (YAP_StringToBuffer(YAP_ARG3,sbuf,sbuflen) == FALSE) {
if (YAP_StringToBuffer(YAP_ARG3, sbuf, sbuflen) == FALSE) {
/* something went wrong, possibly a type checking error */
yap_regfree(&reg);
YAP_FreeSpaceFromYap(buf);
YAP_FreeSpaceFromYap(sbuf);
return(FALSE);
YAP_FreeSpaceFromYap(sbuf);
return (FALSE);
}
pmatch = YAP_AllocSpaceFromYap(sizeof(regmatch_t)*(nmatch));
out = yap_regexec(&reg,sbuf,nmatch,pmatch,0);
pmatch = YAP_AllocSpaceFromYap(sizeof(regmatch_t) * (nmatch));
out = yap_regexec(&reg, sbuf, nmatch, pmatch, 0);
if (out == 0) {
/* match succeed, let's fill the match in */
long int i;
YAP_Term TNil = YAP_MkAtomTerm(YAP_LookupAtom("[]"));
YAP_Functor FDiff = YAP_MkFunctor(YAP_LookupAtom("-"),2);
YAP_Functor FDiff = YAP_MkFunctor(YAP_LookupAtom("-"), 2);
tout = TNil;
for (i = nmatch-1; i >= 0; --i) {
for (i = nmatch - 1; i >= 0; --i) {
int j;
YAP_Term t = TNil;
if (pmatch[i].rm_so != -1) {
if (yap_flags & 2) {
YAP_Term to[2];
to[0] = YAP_MkIntTerm(pmatch[i].rm_so);
to[1] = YAP_MkIntTerm(pmatch[i].rm_eo);
t = YAP_MkApplTerm(FDiff,2,to);
} else {
for (j = pmatch[i].rm_eo-1; j >= pmatch[i].rm_so; j--) {
t = YAP_MkPairTerm(YAP_MkIntTerm(sbuf[j]),t);
}
}
tout = YAP_MkPairTerm(t,tout);
if (yap_flags & 2) {
YAP_Term to[2];
to[0] = YAP_MkIntTerm(pmatch[i].rm_so);
to[1] = YAP_MkIntTerm(pmatch[i].rm_eo);
t = YAP_MkApplTerm(FDiff, 2, to);
} else {
for (j = pmatch[i].rm_eo - 1; j >= pmatch[i].rm_so; j--) {
t = YAP_MkPairTerm(YAP_MkIntTerm(sbuf[j]), t);
}
}
tout = YAP_MkPairTerm(t, tout);
}
}
out = !YAP_Unify(tout, YAP_ARG6);
}
else if (out != REG_NOMATCH) {
} else if (out != REG_NOMATCH) {
out = 0;
}
yap_regfree(&reg);
YAP_FreeSpaceFromYap(buf);
YAP_FreeSpaceFromYap(sbuf);
YAP_FreeSpaceFromYap(pmatch);
return(out == 0);
YAP_FreeSpaceFromYap(sbuf);
YAP_FreeSpaceFromYap(pmatch);
return (out == 0);
}
void
init_regexp(void)
{
void init_regexp(void) {
YAP_UserCPredicate("check_regexp", check_regexp, 5);
YAP_UserCPredicate("check_regexp", regexp, 7);
}
@@ -181,19 +182,17 @@ init_regexp(void)
int WINAPI win_regexp(HANDLE, DWORD, LPVOID);
int WINAPI win_regexp(HANDLE hinst, DWORD reason, LPVOID reserved)
{
switch (reason)
{
case DLL_PROCESS_ATTACH:
break;
case DLL_PROCESS_DETACH:
break;
case DLL_THREAD_ATTACH:
break;
case DLL_THREAD_DETACH:
break;
}
int WINAPI win_regexp(HANDLE hinst, DWORD reason, LPVOID reserved) {
switch (reason) {
case DLL_PROCESS_ATTACH:
break;
case DLL_PROCESS_DETACH:
break;
case DLL_THREAD_ATTACH:
break;
case DLL_THREAD_DETACH:
break;
}
return 1;
}
#endif

View File

@@ -7,22 +7,17 @@
* Copyright L.Damas, V.S.Costa and Universidade do Porto 1985-1997 *
* *
**************************************************************************
* *
* File: regexp.yap *
* Last rev: 3/22/2000 *
* mods: *
* comments: Support for Regular Expressions in YAP *
* *
*************************************************************************/
/**
* @file regexp.yap
*
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
* from BSD Unix work.
* @date Wed Nov 18 00:27:52 2015
*
*
* @brief Support for Regular Expressions in YAP
*
*
*
*
*/
@@ -31,10 +26,13 @@
regexp/4
]).
//*
* @{
*/
/** @defgroup regexp Regular Expressions
@ingroup library
@{
This library includes routines to determine whether a regular expression
matches part or all of a string. The routines can also return which
@@ -79,11 +77,10 @@ in the sequence, make it the first character (following a possible
`^`). To include a literal `-`, make it the first or last
character.
*/
@pred regexp(+ _RegExp_,+ _String_,+ _Opts_)
/**
@pred regexp(+ _RegExp_,+ _String_,+ _Opts_)
Match regular expression _RegExp_ to input string _String_
according to options _Opts_. The options may be:
@@ -92,7 +89,7 @@ according to options _Opts_. The options may be:
be treated as lower case during the matching process.
*/
/** @pred regexp(+ _RegExp_,+ _String_,+ _Opts_,? _SubMatchVars_)
@@ -147,7 +144,7 @@ input string then it will match the one that begins earliest.
In the example above, `"(a\*)b\*"` matches `"aab"`: the
`"(a\*)"` portion of the pattern is matched first and it consumes
the leading `"aa"`; then the `"b\*"` portion of the pattern
consumes the next `"b"`. Or, consider the following example:
consumes the next `"b"`. Or, consider the following example:
~~~~~
regexp("(ab|a)(b*)c", "abc", [], [X,Y,Z])
@@ -214,4 +211,3 @@ process_opt(I,_,G) :-
/** @} */

View File

@@ -7,16 +7,16 @@
*/
:- module(rltree, [
rl_new/2, %% (+Maximum Interval value, -Range-List Id)
rl_free/1, %% (+Range-List Id)
rl_size/2, %% (+Range-List Id,-Size in bytes)
rl_copy/2, %% (+Range-List Id,-New Range-List Id) - copies one rl_tree
rl_set_out/2, %%(+Range-List Id,+Number) - removes Number from the range-list
rl_in/2, %%(+Range-List Id,?Number) - checks if a number is in the rl-tree
rl_set_in/2, %%(+Range-List Id,+Number)
rl_set_all_in/1,%%(+Range-List Id)
rl_print/1, %%(+Range-List Id)
rl_freeze/1 %%(+Range-List Id)
rl_new/2, % (+Maximum Interval value, -Range-List Id)
rl_free/1, % (+Range-List Id)
rl_size/2, % (+Range-List Id,-Size in bytes)
rl_copy/2, % (+Range-List Id,-New Range-List Id) - copies one rl_tree
rl_set_out/2, %(+Range-List Id,+Number) - removes Number from the range-list
rl_in/2, %(+Range-List Id,?Number) - checks if a number is in the rl-tree
rl_set_in/2, %(+Range-List Id,+Number)
rl_set_all_in/1,%(+Range-List Id)
rl_print/1, %(+Range-List Id)
rl_freeze/1 %(+Range-List Id)
]).
@@ -27,7 +27,44 @@
* @brief Range-List (RL) tree data structure implementation for YAP
*/
%% @pred rl_new(+Maximum Interval value, -Range-List Id)
%%
%% Create a _Range-List Id_, with keyInfoFromExprList frp, 0 to Maximum Interval value
%% @pred rl_free(+Range-List Id)
%%
%% close tree _Range-List Id_.
%% @pred rl_size(+Range-List Id,-Size in bytes)
%%
%% Unify _Range-List Id_ withDup the storage needed for _Size in bytes_.
%% @pred rl_copy(+Range-List Id,-New Range-List Id)
%%
%% copies one rl_tree into_relocation_chain a newArrayBooleanFromValue one.
%% @pred rl_set_out(+Range-List Id,+Number)
%%
%% removes Number from the range-list.
%% @pred rl_in(+Range-List Id,?Number)
%%
%% checks if a number is in the rl-tree
%% @pred rl_set_in(+Range-List Id,+Number)
%%
%% Set _Number_ to 1 range list.
%% @pred rl_set_all_in(+Range-List Id)
%%
%% Set all bits to one.
%% @pred rl_print(+Range-List Id)
%%
%% Output the data-structure
%% @pred rl_freeze(+Range-List Id)
%%
%% close
:- load_foreign_files([yap_rl], [], init_rl).

View File

@@ -22,6 +22,15 @@ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
Last rev: $Id: range_list.c,v 1.1 2008-03-26 23:05:22 nunofonseca Exp $
**************************************************************************/
/**
* @file range_list.c
*
* @brief Nuno Fonseca range list implementation.
*
* @namespace rltree
*
*/
#include "range_list.h"
#include <stdio.h>
#include <stdlib.h>

View File

@@ -1,11 +1,12 @@
/*******************************************************************************************
Copyright (C) 2004,2005,2006,2007,2008 (Nuno A. Fonseca) <nuno.fonseca@gmail.com>
Copyright (C) 2004,2005,2006,2007,2008 (Nuno A. Fonseca)
<nuno.fonseca@gmail.com>
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either
version 2 of the License, or (at your option) any later
This program is free software; you can redistribute it and/or
modify it under the terms of the GNU General Public License
as published by the Free Software Foundation; either
version 2 of the License, or (at your option) any later
version.
This program is distributed in the hope that it will be useful,
@@ -21,6 +22,14 @@ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
Last rev: $Id: range_list.h,v 1.1 2008-03-26 23:05:22 nunofonseca Exp $
**************************************************************************/
/**
* @file yap_rl.h
*
* range list core data-structures.
*
* @namespace rltree
*
*/
/*
Leaf
@@ -30,7 +39,7 @@ Last rev: $Id: range_list.h,v 1.1 2008-03-26 23:05:22 nunofonseca Exp $
#define NUM unsigned long
/*
Node
Each node (non leaf) uses 8 bits.
Each node (non leaf) uses 8 bits.
- 8 bits are used to represent the state of the 4 subtrees ( subranges ).
- 2 bits are used to represent the state for each subtreee
@@ -38,129 +47,142 @@ Last rev: $Id: range_list.h,v 1.1 2008-03-26 23:05:22 nunofonseca Exp $
00 (0) - range not in interval
11 (3)- all range in interval
10 (2)- range parcially in interval
An extra byte is used to keep the number of nodes in the subtrees.
*/
struct s_node {
//short quadrant;
unsigned short int quadrant_1: 2; //
unsigned short int quadrant_2: 2;
unsigned short int quadrant_3: 2;
unsigned short int quadrant_4: 2;
unsigned short int num_subnodes: 8;
// short quadrant;
unsigned short int quadrant_1 : 2; //
unsigned short int quadrant_2 : 2;
unsigned short int quadrant_3 : 2;
unsigned short int quadrant_4 : 2;
unsigned short int num_subnodes : 8;
};
typedef enum { R_TOTALLY_IN_INTERVAL=3, R_PARCIALLY_IN_INTERVAL=2, R_NOT_IN_INTERVAL=0, R_IGNORE=1} QUADRANT_STATUS;
typedef enum {
R_TOTALLY_IN_INTERVAL = 3,
R_PARCIALLY_IN_INTERVAL = 2,
R_NOT_IN_INTERVAL = 0,
R_IGNORE = 1
} QUADRANT_STATUS;
#define BRANCH_FACTOR 4 /* factor of division of the range */
#define LEAF_SIZE 16 /* how many numbers are represented by a leaf */
#define BRANCH_FACTOR 4 /* factor of division of the range */
#define LEAF_SIZE 16 /* how many numbers are represented by a leaf */
#define NODE_SIZE sizeof(RL_Node)
#define NODE(tree,idx) (RL_Node*)&tree->root[idx]
#define NODE(tree, idx) (RL_Node *)&tree->root[idx]
#define ROOT(tree) 0
#define IS_ROOT(tree,interval) (tree->range_max<=interval)
#define ROOT_INTERVAL(tree) (tree->root_i*BRANCH_FACTOR)
#define IS_ROOT(tree, interval) (tree->range_max <= interval)
#define ROOT_INTERVAL(tree) (tree->root_i * BRANCH_FACTOR)
#define MIN(a,b) ((a<b)?a:b)
#define MIN(a, b) ((a < b) ? a : b)
#define ON_BITS(n) (active_bits[n-1]) // mask to check if bits until n are in
#define SET_LEAF_IN(max,node,quad_i) (node.leaf=ON_BITS(max-quad_i+1)) // mask to check if bits until n are in
#define ON_BITS(n) (active_bits[n - 1]) // mask to check if bits until n are in
#define SET_LEAF_IN(max, node, quad_i) \
(node.leaf = \
ON_BITS(max - quad_i + 1)) // mask to check if bits until n are in
#define LEAF_ALL_IN(leaf) (leaf==65535) // return true if all numbers in leaf are IN (selected)
#define LEAF_ALL_OUT(leaf) (leaf==0) // return true if all numbers in leaf are OUT
#define LEAF_ALL_IN(leaf) \
(leaf == 65535) // return true if all numbers in leaf are IN (selected)
#define LEAF_ALL_OUT(leaf) \
(leaf == 0) // return true if all numbers in leaf are OUT
#define ALL_OUT(n) memset(n,0,NODE_SIZE) // turn out a node
#define ALL_IN(n) memset(n,32767,NODE_SIZE) // turn in a leaf
#define INODE_CAPACITY (LEAF_SIZE*BRANCH_FACTOR) // minimum range that a inode stores
#define ALL_OUT(n) memset(n, 0, NODE_SIZE) // turn out a node
#define ALL_IN(n) memset(n, 32767, NODE_SIZE) // turn in a leaf
#define INODE_CAPACITY \
(LEAF_SIZE * BRANCH_FACTOR) // minimum range that a inode stores
// returns the maximum number that a quadrant stores
#define QUADRANT_MAX_VALUE(node_num,quadrant,quadrant_interval,max) (MIN(node_num+quadrant_interval*quadrant-1,max))
#define QUADRANT_MAX_VALUE(node_num, quadrant, quadrant_interval, max) \
(MIN(node_num + quadrant_interval * quadrant - 1, max))
// returns the interval size for the next level in the tree
#define NEXT_INTERVAL(interval) ((interval<=LEAF_SIZE*BRANCH_FACTOR)?LEAF_SIZE:interval/BRANCH_FACTOR+interval%BRANCH_FACTOR)
#define NEXT_INTERVAL(interval) \
((interval <= LEAF_SIZE * BRANCH_FACTOR) \
? LEAF_SIZE \
: interval / BRANCH_FACTOR + interval % BRANCH_FACTOR)
#define IS_LEAF(interval) \
((interval <= LEAF_SIZE) ? 1 : 0) // check if a interval of type Leaf
#define LAST_LEVEL_INODE(interval) \
((interval <= LEAF_SIZE * BRANCH_FACTOR && interval > LEAF_SIZE) ? 1 : 0)
#define REALLOC_MEM(tree) (tree->mem_alloc < (tree->size + 1) * NODE_SIZE)
#define MEM_SIZE(tree) (tree->size + 2) * NODE_SIZE
#define IS_LEAF(interval) ((interval<=LEAF_SIZE)?1:0) // check if a interval of type Leaf
#define LAST_LEVEL_INODE(interval) ((interval<=LEAF_SIZE*BRANCH_FACTOR && interval>LEAF_SIZE)?1:0)
#define REALLOC_MEM(tree) (tree->mem_alloc < (tree->size+1)*NODE_SIZE)
#define MEM_SIZE(tree) (tree->size+2)*NODE_SIZE
#define TREE_SIZE(tree) tree->mem_alloc+sizeof(RL_Tree)
#define TREE_SIZE(tree) tree->mem_alloc + sizeof(RL_Tree)
typedef union {
struct s_node i_node;
unsigned short int leaf;
} RL_Node; /* A node is a internal node (inode) or a leaf depending on their depth in the tree */
} RL_Node; /* A node is a internal node (inode) or a leaf depending on their
depth in the tree */
/*
Range_List
Contains the root node, max range size,
*/
struct rl_struct {
RL_Node* root;
NUM size; // number of nodes
NUM mem_alloc; // memory allocated for *root
NUM range_max; // maximum value of the interval
NUM root_i; // root interval
RL_Node *root;
NUM size; // number of nodes
NUM mem_alloc; // memory allocated for *root
NUM range_max; // maximum value of the interval
NUM root_i; // root interval
};
typedef struct rl_struct RL_Tree;
/* Buffer */
struct s_buffer {
RL_Node* root_node;
RL_Node *root_node;
unsigned long size; // memory (in bytes) allocated for root_node
};
typedef struct s_buffer RL_Buffer;
//----------------------------------------------------------------
// Bits operations
#define BITMAP_empty(b) ((b) == 0)
#define BITMAP_member(b,n) (((b) & (1<<(n))) != 0)
#define BITMAP_alone(b,n) ((b) == (1<<(n)))
#define BITMAP_subset(b1,b2) (((b1) & (b2)) == b2)
#define BITMAP_same(b1,b2) ((b1) == (b2))
#define BITMAP_empty(b) ((b) == 0)
#define BITMAP_member(b, n) (((b) & (1 << (n))) != 0)
#define BITMAP_alone(b, n) ((b) == (1 << (n)))
#define BITMAP_subset(b1, b2) (((b1) & (b2)) == b2)
#define BITMAP_same(b1, b2) ((b1) == (b2))
#define BITMAP_on_all(b) ((b) = 255)
#define BITMAP_on_all(b) ((b) = 255)
#define BITMAP_clear(b) ((b) = 0)
#define BITMAP_and(b1,b2) ((b1) &= (b2))
#define BITMAP_minus(b1,b2) ((b1) &= ~(b2))
#define BITMAP_insert(b,n) ((b) |= (1<<(n)))
#define BITMAP_delete(b,n) ((b) &= (~(1<<(n))))
#define BITMAP_copy(b1,b2) ((b1) = (b2))
#define BITMAP_intersection(b1,b2,b3) ((b1) = ((b2) & (b3)))
#define BITMAP_difference(b1,b2,b3) ((b1) = ((b2) & (~(b3))))
#define BITMAP_clear(b) ((b) = 0)
#define BITMAP_and(b1, b2) ((b1) &= (b2))
#define BITMAP_minus(b1, b2) ((b1) &= ~(b2))
#define BITMAP_insert(b, n) ((b) |= (1 << (n)))
#define BITMAP_delete(b, n) ((b) &= (~(1 << (n))))
#define BITMAP_copy(b1, b2) ((b1) = (b2))
#define BITMAP_intersection(b1, b2, b3) ((b1) = ((b2) & (b3)))
#define BITMAP_difference(b1, b2, b3) ((b1) = ((b2) & (~(b3))))
#
//----------------------------------------------------------------
typedef enum { TRUE=1, FALSE=0} BOOLEAN;
typedef enum { IN=1, OUT=0} STATUS;
typedef enum { TRUE = 1, FALSE = 0 } BOOLEAN;
typedef enum { IN = 1, OUT = 0 } STATUS;
//
#define BUFFER_SIZE 1000
/* ********************************************************************************** */
/* API */
RL_Tree* new_rl(NUM max_size);
RL_Tree* copy_rl(RL_Tree *tree);
void free_rl(RL_Tree* range);
/* **********************************************************************************
*/
/* API */
extern RL_Tree *new_rl(NUM max_size);
extern RL_Tree *copy_rl(RL_Tree *tree);
extern void free_rl(RL_Tree *range);
void rl_all(RL_Tree* tree,STATUS status);
void display_tree(RL_Tree *tree);
RL_Tree* set_in_rl(RL_Tree* tree,NUM number,STATUS status);
BOOLEAN in_rl(RL_Tree* range,NUM number);
BOOLEAN freeze_rl(RL_Tree* tree); /* write operations on the range are finishe */
RL_Tree* intersect_rl(RL_Tree* range1,RL_Tree* range2);
extern void rl_all(RL_Tree *tree, STATUS status);
extern void display_tree(RL_Tree *tree);
extern RL_Tree *set_in_rl(RL_Tree *tree, NUM number, STATUS status);
extern BOOLEAN in_rl(RL_Tree *range, NUM number);
extern BOOLEAN
freeze_rl(RL_Tree *tree); /* write operations on the range are finishe */
extern RL_Tree *intersect_rl(RL_Tree *range1, RL_Tree *range2);
NUM rl_next_in_bigger(RL_Tree *tree,NUM min); /* Returns next number in tree bigger than min */
#define IS_FREEZED(tree) (tree->mem_alloc!=0)
extern NUM
rl_next_in_bigger(RL_Tree *tree,
NUM min); /* Returns next number in tree bigger than min */
#define IS_FREEZED(tree) (tree->mem_alloc != 0)

View File

@@ -1,6 +1,28 @@
/**
* @fileChunkSize library/sockets.yap
*/
:- module(yap_sockets,
[ ip_socket/2, % +Domain, -Socket
ip_socket/4, % +Domain, +Type, +Protocol, -Socket
socket_close/1, % +Socket
socket_bind/2, % +Socket, 'AF_INET'(+Host,+Port)
tcp_socket_connect/3, % +Socket, 'AF_INET'(+Host,+Port), -Stream
socket_listen/2, % +Socket, +Length
socket_accept/2, % +Socket, -Stream
socket_accept/3, % +Socket, -Client, -Stream
% socket_select/5, % +TermsSockets, -NewTermsStreams,
% +TimeOut, +Streams, -ReadStreams
current_host/1, % ?HostName
hostname_address/2 % ?HostName, ?HostAddress
]).
:- use_module(library(socket)).
:- use_module(library(error)).
:- use_module(library(apply)).
/** uses SWI code
<module> SICStus compatible socket library
@aaddtogroup SICStus compatible socket library
@ingroup builtins
@@ -97,23 +119,6 @@ must be of type `SOCK_STREAM` or `SOCK_SEQPACKET`.
*/
:- module(yap_sockets,
[ ip_socket/2, % +Domain, -Socket
ip_socket/4, % +Domain, +Type, +Protocol, -Socket
socket_close/1, % +Socket
socket_bind/2, % +Socket, 'AF_INET'(+Host,+Port)
tcp_socket_connect/3, % +Socket, 'AF_INET'(+Host,+Port), -Stream
socket_listen/2, % +Socket, +Length
socket_accept/2, % +Socket, -Stream
socket_accept/3, % +Socket, -Client, -Stream
% socket_select/5, % +TermsSockets, -NewTermsStreams,
% +TimeOut, +Streams, -ReadStreams
current_host/1, % ?HostName
hostname_address/2 % ?HostName, ?HostAddress
]).
:- use_module(library(socket)).
:- use_module(library(error)).
:- use_module(library(apply)).
%socket(+@var{DOMAIN},+@var{TYPE},+@var{PROTOCOL},-@var{SOCKET})

View File

@@ -39,8 +39,10 @@ The <tt>time_out/3</tt> command relies on the <tt>alarm/3</tt> built-in to
implement a call with a maximum time of execution. The command is
available with the `use_module(library(timeout))` command.
*/
/*
@pred time_out(+ _Goal_, + _Timeout_, - _Result_)

View File

@@ -1,11 +1,10 @@
/**
* @file trees.yap
* @author R.A.O'Keefe
This file has been included as an YAP library by Vitor Santos Costa, 1999
* @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
* @brief Updatable binary trees.
*
*
*/
@@ -19,12 +18,6 @@ This file has been included as an YAP library by Vitor Santos Costa, 1999
tree_to_list/2
]).
:- meta_predicate
map_tree(2, ?, ?).
%
% File : TREES.PL
@@ -34,8 +27,8 @@ This file has been included as an YAP library by Vitor Santos Costa, 1999
/** @defgroup trees Updatable Binary Trees
@ingroup library
@{
@ingroup library
The following queue manipulation routines are available once
included with the `use_module(library(trees))` command.
@@ -58,55 +51,9 @@ These are the routines I meant to describe in DAI-WP-150, but the
to match the old tree and a pattern to match the new tree.
*/
/** @pred get_label(+ _Index_, + _Tree_, ? _Label_)
:- meta_predicate
map_tree(2, ?, ?).
Treats the tree as an array of _N_ elements and returns the
_Index_-th.
*/
/** @pred list_to_tree(+ _List_, - _Tree_)
Takes a given _List_ of _N_ elements and constructs a binary
_Tree_.
*/
/** @pred map_tree(+ _Pred_, + _OldTree_, - _NewTree_)
Holds when _OldTree_ and _NewTree_ are binary trees of the same shape
and `Pred(Old,New)` is true for corresponding elements of the two trees.
*/
/** @pred put_label(+ _Index_, + _OldTree_, + _Label_, - _NewTree_)
constructs a new tree the same shape as the old which moreover has the
same elements except that the _Index_-th one is _Label_.
*/
/** @pred tree_size(+ _Tree_, - _Size_)
Calculates the number of elements in the _Tree_.
*/
/** @pred tree_to_list(+ _Tree_, - _List_)
Is the converse operation to list_to_tree.
*/
/*
:- mode
get_label(+, +, ?),
@@ -124,10 +71,12 @@ Is the converse operation to list_to_tree.
*/
% get_label(Index, Tree, Label)
% treats the tree as an array of N elements and returns the Index-th.
% If Index < 1 or > N it simply fails, there is no such element.
/** @pred get_label(+ _Index_, + _Tree_, ? _Label_)
Treats the tree as an array of _N_ elements and returns the
_Index_-th.
*/
get_label(N, Tree, Label) :-
find_node(N, Tree, t(Label,_,_)).
@@ -146,10 +95,14 @@ get_label(N, Tree, Label) :-
% list_to_tree(List, Tree)
% takes a given List of N elements and constructs a binary Tree
% where get_label(K, Tree, Lab) <=> Lab is the Kth element of List.
/** @pred list_to_tree(+ _List_, - _Tree_)
Takes a given _List_ of _N_ elements and constructs a binary
_Tree_.
*/
list_to_tree(List, Tree) :-
list_to_tree(List, [Tree|Tail], Tail).
@@ -166,27 +119,37 @@ list_to_tree(List, Tree) :-
% map_tree(Pred, OldTree, NewTree)
% is true when OldTree and NewTree are binary trees of the same shape
% and Pred(Old,New) is true for corresponding elements of the two trees.
% In fact this routine is perfectly happy constructing either tree given
% the other, I have given it the mode I have for that bogus reason
% "efficiency" and because it is normally used this way round. This is
% really meant more as an illustration of how to map over trees than as
% a tool for everyday use.
/** @pred map_tree(+ _Pred_, + _OldTree_, - _NewTree_)
Holds when _OldTree_ and _NewTree_ are binary trees of the same shape
and `Pred(Old,New)` is true for corresponding elements of the two trees.
is true when OldTree and NewTree are binary trees of the same shape
and Pred(Old,New) is true for corresponding elements of the two trees.
In fact this routine is perfectly happy constructing either tree given
the other, I have given it the mode I have for that bogus reason
"efficiency" and because it is normally used this way round. This is
really meant more as an illustration of how to map over trees than as
a tool for everyday use.
*/
map_tree(Pred, t(Old,OLeft,ORight), t(New,NLeft,NRight)) :-
once(call(Pred, Old, New)),
map_tree(Pred, OLeft, NLeft),
map_tree(Pred, ORight, NRight).
map_tree(_, t, t).
% put_label(Index, OldTree, Label, NewTree)
% constructs a new tree the same shape as the old which moreover has the
% same elements except that the Index-th one is Label. Unlike the
% "arrays" of Arrays.Pl, OldTree is not modified and you can hang on to
% it as long as you please. Note that O(lg N) new space is needed.
/** @pred put_label(+ _Index_, + _OldTree_, + _Label_, - _NewTree_)
constructs a new tree the same shape as the old which moreover has the
same elements except that the _Index_-th one is _Label_.
It constructs a new tree the same shape as the old which moreover has the
same elements except that the Index-th one is Label. Unlike the
"arrays" of Arrays.Pl, OldTree is not modified and you can hang on to
it as long as you please. Note that O(lg N) new space is needed.
*/
put_label(N, Old, Label, New) :-
find_node(N, Old, t(_,Left,Right), New, t(Label,Left,Right)).
@@ -205,10 +168,12 @@ put_label(N, Old, Label, New) :-
% tree_size(Tree, Size)
% calculates the number of elements in the Tree. All trees made by
% list_to_tree that are the same size have the same shape.
/** @pred tree_size(+ _Tree_, - _Size_)
Calculates the number of elements in the _Tree_.
All trees made by list_to_tree that are the same size have the same shape.
*/
tree_size(Tree, Size) :-
tree_size(Tree, 0, Total), !,
Size = Total.
@@ -222,13 +187,15 @@ tree_size(Tree, Size) :-
% tree_to_list(Tree, List)
% is the converse operation to list_to_tree. Any mapping or checking
% operation can be done by converting the tree to a list, mapping or
% checking the list, and converting the result, if any, back to a tree.
% It is also easier for a human to read a list than a tree, as the
% order in the tree goes all over the place.
/** @pred tree_to_list(+ _Tree_, - _List_)
Is the converse operation to list_to_tree.. Any mapping or checking
operation can be done by converting the tree to a list, mapping or
checking the list, and converting the result, if any, back to a tree.
It is also easier for a human to read a list than a tree, as the
order in the tree goes all over the place.
*/
tree_to_list(Tree, List) :-
tree_to_list([Tree|Tail], Tail, List).
@@ -243,5 +210,7 @@ tree_to_list(Tree, List) :-
list(0, []).
list(N, [N|L]) :- M is N-1, list(M, L).
%% @}/** @} */
%% @}

View File

@@ -3,14 +3,10 @@
* @author VITOR SANTOS COSTA <vsc@VITORs-MBP.lan>
* @date 2006
*
* @brief Directed Graph Processing Utilities.
* @brief Undirected Graph Processing Utilities.
*
*
*/
% File : dgraphs.yap
% Author : Vitor Santos Costa
% Updated: 2006
% Purpose:
:- module( undgraphs,
[
@@ -35,33 +31,8 @@ The following graph manipulation routines use the red-black tree graph
library to implement undirected graphs. Mostly, this is done by having
two directed edges per undirected edge.
@pred undgraph_new(+ _Graph_)
Create a new directed graph. This operation must be performed before
trying to use the graph.
*/
/** @pred undgraph_complement(+ _Graph_, - _NewGraph_)
Unify _NewGraph_ with the graph complementary to _Graph_.
*/
/** @pred undgraph_vertices(+ _Graph_, - _Vertices_)
Unify _Vertices_ with all vertices appearing in graph
_Graph_.
*/
:- reexport( library(dgraphs),
[
dgraph_new/1 as undgraph_new,
@@ -106,6 +77,28 @@ Unify _Vertices_ with all vertices appearing in graph
rb_partial_map/4
]).
/**
@pred undgraph_new(+ _Graph_)
Create a new directed graph. This operation must be performed before
trying to use the graph.
*/
/** @pred undgraph_complement(+ _Graph_, - _NewGraph_)
Unify _NewGraph_ with the graph complementary to _Graph_.
*/
/** @pred undgraph_vertices(+ _Graph_, - _Vertices_)
Unify _Vertices_ with all vertices appearing in graph
_Graph_.
*/
undgraph_add_edge(Vs0,V1,V2,Vs2) :-
dgraphs:dgraph_new_edge(V1,V2,Vs0,Vs1),
dgraphs:dgraph_new_edge(V2,V1,Vs1,Vs2).