Merge branch 'master' of https://github.com/vscosta/yap-6.3
This commit is contained in:
commit
670eacc823
@ -18,6 +18,8 @@
|
|||||||
blank/3,
|
blank/3,
|
||||||
split/2,
|
split/2,
|
||||||
split/3,
|
split/3,
|
||||||
|
split/4,
|
||||||
|
split/5,
|
||||||
split_unquoted/3,
|
split_unquoted/3,
|
||||||
fields/2,
|
fields/2,
|
||||||
fields/3,
|
fields/3,
|
||||||
@ -27,6 +29,7 @@
|
|||||||
file_filter/3,
|
file_filter/3,
|
||||||
file_select/2,
|
file_select/2,
|
||||||
file_filter_with_initialization/5,
|
file_filter_with_initialization/5,
|
||||||
|
file_filter_with_start_end/5,
|
||||||
file_filter_with_initialization/5 as file_filter_with_init,
|
file_filter_with_initialization/5 as file_filter_with_init,
|
||||||
process/2
|
process/2
|
||||||
]).
|
]).
|
||||||
@ -49,6 +52,7 @@ available by loading the
|
|||||||
filter(+,+,2),
|
filter(+,+,2),
|
||||||
file_filter(+,+,2),
|
file_filter(+,+,2),
|
||||||
file_filter_with_initialization(+,+,2,+,:),
|
file_filter_with_initialization(+,+,2,+,:),
|
||||||
|
file_filter_with_start_end(+,+,2,2,2),
|
||||||
process(+,1).
|
process(+,1).
|
||||||
|
|
||||||
:- use_module(library(lists),
|
:- use_module(library(lists),
|
||||||
@ -188,28 +192,73 @@ split_at_blank(SplitCodes, More) -->
|
|||||||
split_at_blank(SplitCodes, More).
|
split_at_blank(SplitCodes, More).
|
||||||
split_at_blank(SplitCodes, [[C|New]| More]) -->
|
split_at_blank(SplitCodes, [[C|New]| More]) -->
|
||||||
[C], !,
|
[C], !,
|
||||||
split(SplitCodes, New, More).
|
split_(SplitCodes, New, More).
|
||||||
split_at_blank(_, []) --> [].
|
split_at_blank(_, []) --> [].
|
||||||
|
|
||||||
split(SplitCodes, [], More) -->
|
split_(SplitCodes, [], More) -->
|
||||||
[C],
|
[C],
|
||||||
{ member(C, SplitCodes) }, !,
|
{ member(C, SplitCodes) }, !,
|
||||||
split_at_blank(SplitCodes, More).
|
split_at_blank(SplitCodes, More).
|
||||||
split(SplitCodes, [C|New], Set) -->
|
split_(SplitCodes, [C|New], Set) -->
|
||||||
[C], !,
|
[C], !,
|
||||||
split(SplitCodes, New, Set).
|
split_(SplitCodes, New, Set).
|
||||||
split(_, [], []) --> [].
|
split_(_, [], []) --> [].
|
||||||
|
|
||||||
/** @pred split_unquoted(+ _Line_,+ _Separators_,- _Split_)
|
|
||||||
|
split(Text, SplitCodes, DoubleQs, SingleQs, Strings) :-
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, Strings, Text, []).
|
||||||
|
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, Strings) -->
|
||||||
|
[C],
|
||||||
|
!,
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, Strings, C).
|
||||||
|
split_element(_SplitCodes, _DoubleQs, _SingleQs, []) --> !.
|
||||||
|
split_element(_SplitCodes, _DoubleQs, _SingleQs, [[]]) --> [].
|
||||||
|
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, Strings, C) -->
|
||||||
|
{ member( C, SingleQs ) },
|
||||||
|
!,
|
||||||
|
[C2],
|
||||||
|
{ Strings = [[C2|String]|More] },
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, [String| More]).
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, [[]|Strings], C) -->
|
||||||
|
{ member( C, SplitCodes ) },
|
||||||
|
!,
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, Strings).
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, Strings, C) -->
|
||||||
|
{ member( C, DoubleQs ) } ,
|
||||||
|
!,
|
||||||
|
split_within(SplitCodes, C-DoubleQs, SingleQs, Strings).
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, [[C|String]|Strings], C) -->
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, [String|Strings]).
|
||||||
|
|
||||||
|
split_within(SplitCodes, DoubleQs, SingleQs, Strings) -->
|
||||||
|
[C],
|
||||||
|
split_within(SplitCodes, DoubleQs, SingleQs, Strings, C).
|
||||||
|
|
||||||
|
split_within(SplitCodes, DoubleQs, SingleQs, Strings, C) -->
|
||||||
|
{ member( C, SingleQs ) },
|
||||||
|
!,
|
||||||
|
[C2],
|
||||||
|
{ Strings = [[C2|String]|More] },
|
||||||
|
split_within(SplitCodes, DoubleQs, SingleQs, [String| More]).
|
||||||
|
split_within(SplitCodes, DoubleQs, C-SingleQs, Strings, C) -->
|
||||||
|
!,
|
||||||
|
split_element(SplitCodes, DoubleQs, SingleQs, Strings).
|
||||||
|
split_within(SplitCodes, DoubleQs, SingleQs, [[C|String]|Strings], C) -->
|
||||||
|
split_within(SplitCodes, DoubleQs, SingleQs, [String|Strings]).
|
||||||
|
|
||||||
|
|
||||||
|
/** @pred split_quoted(+ _Line_,+ _Separators_, GroupQuotes, SingleQuotes, - _Split_)
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
Unify _Words_ with a set of strings obtained from _Line_ by
|
Unify _Words_ with a set of strings obtained from _Line_ by
|
||||||
using the character codes in _Separators_ as separators, but treat text within double quotes as a single unit. As an
|
using the character codes in _Separators_ as separators, but treat text within quotes as a single unit. As an
|
||||||
example, consider:
|
example, consider:
|
||||||
|
|
||||||
~~~~~{.prolog}
|
~~~~~{.prolog}
|
||||||
?- split("Hello * I \"am free\""," *",S).
|
?- split_quoted("Hello * I \"am free\""," *",S).
|
||||||
|
|
||||||
S = ["Hello","I","am free"] ?
|
S = ["Hello","I","am free"] ?
|
||||||
|
|
||||||
@ -217,31 +266,6 @@ no
|
|||||||
~~~~~
|
~~~~~
|
||||||
|
|
||||||
*/
|
*/
|
||||||
split_unquoted(String, SplitCodes, Strings) :-
|
|
||||||
split_unquoted_at_blank(SplitCodes, Strings, String, []).
|
|
||||||
|
|
||||||
split_unquoted_at_blank(SplitCodes, [[0'"|New]|More]) --> %0'"
|
|
||||||
"\"",
|
|
||||||
split_quoted(New, More),
|
|
||||||
split_unquoted_at_blank(SplitCodes, More).
|
|
||||||
split_unquoted_at_blank(SplitCodes, More) -->
|
|
||||||
[C],
|
|
||||||
{ member(C, SplitCodes) }, !,
|
|
||||||
split_unquoted_at_blank(SplitCodes, More).
|
|
||||||
split_unquoted_at_blank(SplitCodes, [[C|New]| More]) -->
|
|
||||||
[C], !,
|
|
||||||
split_unquoted(SplitCodes, New, More).
|
|
||||||
split_unquoted_at_blank(_, []) --> [].
|
|
||||||
|
|
||||||
split_unquoted(SplitCodes, [], More) -->
|
|
||||||
[C],
|
|
||||||
{ member(C, SplitCodes) }, !,
|
|
||||||
split_unquoted_at_blank(SplitCodes, More).
|
|
||||||
split_unquoted(SplitCodes, [C|New], Set) -->
|
|
||||||
[C], !,
|
|
||||||
split_unquoted(SplitCodes, New, Set).
|
|
||||||
split_unquoted(_, [], []) --> [].
|
|
||||||
|
|
||||||
split_quoted( [0'"], _More) --> %0'"
|
split_quoted( [0'"], _More) --> %0'"
|
||||||
"\"".
|
"\"".
|
||||||
split_quoted( [0'\\ ,C|New], More) -->
|
split_quoted( [0'\\ ,C|New], More) -->
|
||||||
@ -402,6 +426,23 @@ file_filter_with_initialization(Inp, Out, Command, FormatString, Parameters) :-
|
|||||||
close(StreamOut).
|
close(StreamOut).
|
||||||
|
|
||||||
|
|
||||||
|
/** @pred file_filter_with_start_end(+ FileIn, + FileOut, + Goal, + StartGoal, + EndGoal)
|
||||||
|
|
||||||
|
Same as file_filter/3, but before starting the filter execute
|
||||||
|
_StartGoal_, and call _ENdGoal_ as an epilog.
|
||||||
|
|
||||||
|
The input stream are always accessible through `filter_output` and `filter_input`.
|
||||||
|
*/
|
||||||
|
file_filter_with_start_end(Inp, Out, Command, StartGoal, EndGoal) :-
|
||||||
|
open(Inp, read, StreamInp, [alias(filter_input)]),
|
||||||
|
open(Out, write, StreamOut, [alias(filter_output)]),
|
||||||
|
call( StartGoal, StreamInp, StreamOut ),
|
||||||
|
filter(StreamInp, StreamOut, Command),
|
||||||
|
call( EndGoal, StreamInp, StreamOut ),
|
||||||
|
close(StreamInp),
|
||||||
|
close(StreamOut).
|
||||||
|
|
||||||
|
|
||||||
/**
|
/**
|
||||||
* @pred file_select(+ _FileIn_, + _Goal_) is meta
|
* @pred file_select(+ _FileIn_, + _Goal_) is meta
|
||||||
*
|
*
|
||||||
|
@ -17,6 +17,7 @@
|
|||||||
checklist/2,
|
checklist/2,
|
||||||
checknodes/2,
|
checknodes/2,
|
||||||
convlist/3,
|
convlist/3,
|
||||||
|
convlist/4,
|
||||||
foldl/4,
|
foldl/4,
|
||||||
foldl/5,
|
foldl/5,
|
||||||
foldl/6,
|
foldl/6,
|
||||||
@ -128,6 +129,7 @@ triple. See the example above.
|
|||||||
maplist(3,+,+,-),
|
maplist(3,+,+,-),
|
||||||
maplist(4,+,+,+,-),
|
maplist(4,+,+,+,-),
|
||||||
convlist(2,+,-),
|
convlist(2,+,-),
|
||||||
|
convlist(3,?,?,?),
|
||||||
mapnodes(2,+,-),
|
mapnodes(2,+,-),
|
||||||
mapnodes_list(2,+,-),
|
mapnodes_list(2,+,-),
|
||||||
checknodes(1,+),
|
checknodes(1,+),
|
||||||
@ -351,6 +353,29 @@ convlist(Pred, [Old|Olds], NewList) :-
|
|||||||
convlist(Pred, [_|Olds], News) :-
|
convlist(Pred, [_|Olds], News) :-
|
||||||
convlist(Pred, Olds, News).
|
convlist(Pred, Olds, News).
|
||||||
|
|
||||||
|
/**
|
||||||
|
convlist(: Pred, ? ListIn, ?ExtraList, ? ListOut) @anchor convlist
|
||||||
|
|
||||||
|
A combination of maplist/4 and selectlist/3: _ListIn_, _ListExtra_,
|
||||||
|
and _ListOut_ are the sublists so that the predicate _Pred_ succeeds.
|
||||||
|
|
||||||
|
ROK: convlist(Rewrite, OldList, NewList)
|
||||||
|
is a sort of hybrid of maplist/3 and sublist/3.
|
||||||
|
Each element of NewList is the image under Rewrite of some
|
||||||
|
element of OldList, and order is preserved, but elements of
|
||||||
|
OldList on which Rewrite is undefined (fails) are not represented.
|
||||||
|
Thus if foo(X,Y) :- integer(X), Y is X+1.
|
||||||
|
then convlist(foo, [1,a,0,joe(99),101], [2,1,102]).
|
||||||
|
*/
|
||||||
|
convlist(_, [], []).
|
||||||
|
convlist(Pred, [Old|Olds], NewList) :-
|
||||||
|
call(Pred, Old, New),
|
||||||
|
!,
|
||||||
|
NewList = [New|News],
|
||||||
|
convlist(Pred, Olds, News).
|
||||||
|
convlist(Pred, [_|Olds], News) :-
|
||||||
|
convlist(Pred, Olds, News).
|
||||||
|
|
||||||
/**
|
/**
|
||||||
mapnodes(+ _Pred_, + _TermIn_, ? _TermOut_)
|
mapnodes(+ _Pred_, + _TermIn_, ? _TermOut_)
|
||||||
|
|
||||||
@ -960,6 +985,29 @@ goal_expansion(convlist(Meta, ListIn, ListOut), Mod:Goal) :-
|
|||||||
RecursiveCall)
|
RecursiveCall)
|
||||||
], Mod).
|
], Mod).
|
||||||
|
|
||||||
|
goal_expansion(convlist(Meta, ListIn, ListExtra, ListOut), Mod:Goal) :-
|
||||||
|
goal_expansion_allowed,
|
||||||
|
callable(Meta),
|
||||||
|
prolog_load_context(module, Mod),
|
||||||
|
aux_preds(Meta, MetaVars, Pred, PredVars, Proto),
|
||||||
|
!,
|
||||||
|
% the new goal
|
||||||
|
pred_name(convlist, 4, Proto, GoalName),
|
||||||
|
append(MetaVars, [ListIn, ListExtra, ListOut], GoalArgs),
|
||||||
|
Goal =.. [GoalName|GoalArgs],
|
||||||
|
% the new predicate declaration
|
||||||
|
HeadPrefix =.. [GoalName|PredVars],
|
||||||
|
append_args(HeadPrefix, [[], [], []], Base),
|
||||||
|
append_args(HeadPrefix, [[In|Ins], [Extra|Extras], Outs], RecursionHead),
|
||||||
|
append_args(Pred, [In, Extra, Out], Apply),
|
||||||
|
append_args(HeadPrefix, [Ins, Extras, NOuts], RecursiveCall),
|
||||||
|
compile_aux([
|
||||||
|
Base,
|
||||||
|
(RecursionHead :-
|
||||||
|
(Apply -> Outs = [Out|NOuts]; Outs = NOuts),
|
||||||
|
RecursiveCall)
|
||||||
|
], Mod).
|
||||||
|
|
||||||
goal_expansion(sumlist(Meta, List, AccIn, AccOut), Mod:Goal) :-
|
goal_expansion(sumlist(Meta, List, AccIn, AccOut), Mod:Goal) :-
|
||||||
goal_expansion_allowed,
|
goal_expansion_allowed,
|
||||||
callable(Meta),
|
callable(Meta),
|
||||||
|
@ -1,31 +0,0 @@
|
|||||||
/* Define to 1 if you have the <openssl/ripemd.h> header file. */
|
|
||||||
#ifndef HAVE_APACHE2_UTIL_MD5_H
|
|
||||||
/* #undef HAVE_APACHE2_UTIL_MD5_H */
|
|
||||||
#endif
|
|
||||||
|
|
||||||
/* Define to 1 if you have the <openssl/ripemd.h> header file. */
|
|
||||||
#ifndef HAVE_APR_1_APR_MD5_H
|
|
||||||
#define HAVE_APR_1_APR_MD5_H 1
|
|
||||||
#endif
|
|
||||||
|
|
||||||
|
|
||||||
/* Define to 1 if you have the <openssl/md5.h> header file. */
|
|
||||||
#ifndef HAVE_OPENSSL_MD5_H
|
|
||||||
/* #undef HAVE_OPENSSL_MD5_H */
|
|
||||||
#endif
|
|
||||||
|
|
||||||
/* Define to 1 if you have the <openssl/ripemd.h> header file. */
|
|
||||||
#ifndef HAVE_OPENSSL_RIPEMD_H
|
|
||||||
/* #undef HAVE_OPENSSL_RIPEMD_H */
|
|
||||||
#endif
|
|
||||||
|
|
||||||
/* "Define if you have the crypt function." */
|
|
||||||
#ifndef HAVE_CRYPT
|
|
||||||
/* #undef HAVE_CRYPT */
|
|
||||||
#endif
|
|
||||||
|
|
||||||
/* Define to 1 if you have the <crypt.h> header file. */
|
|
||||||
#ifndef HAVE_CRYPT_H
|
|
||||||
/* #undef HAVE_CRYPT_H */
|
|
||||||
#endif
|
|
||||||
|
|
1
os/mem.c
1
os/mem.c
@ -225,6 +225,7 @@ int Yap_open_buf_write_stream(encoding_t enc, memBufSource src) {
|
|||||||
#endif
|
#endif
|
||||||
#else
|
#else
|
||||||
st->nbuf = st->u.mem_string.buf = malloc(PLGETC_BUF_SIZE);
|
st->nbuf = st->u.mem_string.buf = malloc(PLGETC_BUF_SIZE);
|
||||||
|
st->u.mem_string.src == MEM_BUF_MALLOC;
|
||||||
st->u.mem_string.src = 1;
|
st->u.mem_string.src = 1;
|
||||||
st->u.mem_string.max_size = PLGETC_BUF_SIZE - 1;
|
st->u.mem_string.max_size = PLGETC_BUF_SIZE - 1;
|
||||||
st->u.mem_string.pos = 0;
|
st->u.mem_string.pos = 0;
|
||||||
|
@ -110,11 +110,11 @@ static void clean_vars(VarEntry *p) {
|
|||||||
#ifdef O_QUASIQUOTATIONS
|
#ifdef O_QUASIQUOTATIONS
|
||||||
/** '$qq_open'(+QQRange, -Stream) is det.
|
/** '$qq_open'(+QQRange, -Stream) is det.
|
||||||
|
|
||||||
Opens a quasi-quoted memory range.
|
Opens a quasi-quoted memory range.
|
||||||
|
|
||||||
@arg QQRange is a term '$quasi_quotation'(ReadData, Start, Length)
|
@arg QQRange is a term '$quasi_quotation'(ReadData, Start, Length)
|
||||||
@arg Stream is a UTF-8 encoded string, whose position indication
|
@arg Stream is a UTF-8 encoded string, whose position indication
|
||||||
reflects the location in the real file.
|
reflects the location in the real file.
|
||||||
*/
|
*/
|
||||||
|
|
||||||
static Int qq_open(USES_REGS1) {
|
static Int qq_open(USES_REGS1) {
|
||||||
@ -183,7 +183,7 @@ static int parse_quasi_quotations(ReadData _PL_rd ARG_LD) {
|
|||||||
|
|
||||||
#define READ_DEFS() \
|
#define READ_DEFS() \
|
||||||
PAR("comments", list_filler, READ_COMMENTS) \
|
PAR("comments", list_filler, READ_COMMENTS) \
|
||||||
, PAR("module", isatom, READ_MODULE), PAR("priority", nat, READ_PRIORITY), \
|
, PAR("module", isatom, READ_MODULE), PAR("priority", nat, READ_PRIORITY), \
|
||||||
PAR("quasi_quotations", filler, READ_QUASI_QUOTATIONS), \
|
PAR("quasi_quotations", filler, READ_QUASI_QUOTATIONS), \
|
||||||
PAR("term_position", filler, READ_TERM_POSITION), \
|
PAR("term_position", filler, READ_TERM_POSITION), \
|
||||||
PAR("syntax_errors", isatom, READ_SYNTAX_ERRORS), \
|
PAR("syntax_errors", isatom, READ_SYNTAX_ERRORS), \
|
||||||
@ -345,7 +345,7 @@ static Term syntax_error(TokEntry *errtok, int sno, Term cmod) {
|
|||||||
}
|
}
|
||||||
}
|
}
|
||||||
if (tok->TokNext) {
|
if (tok->TokNext) {
|
||||||
tok = tok->TokNext;
|
tok = tok->TokNext;
|
||||||
} else {
|
} else {
|
||||||
endline = MkIntegerTerm(tok->TokPos);
|
endline = MkIntegerTerm(tok->TokPos);
|
||||||
tok = NULL;
|
tok = NULL;
|
||||||
@ -1017,7 +1017,7 @@ static Int read_term(
|
|||||||
|
|
||||||
#define READ_CLAUSE_DEFS() \
|
#define READ_CLAUSE_DEFS() \
|
||||||
PAR("comments", list_filler, READ_CLAUSE_COMMENTS) \
|
PAR("comments", list_filler, READ_CLAUSE_COMMENTS) \
|
||||||
, PAR("module", isatom, READ_CLAUSE_MODULE), \
|
, PAR("module", isatom, READ_CLAUSE_MODULE), \
|
||||||
PAR("variable_names", filler, READ_CLAUSE_VARIABLE_NAMES), \
|
PAR("variable_names", filler, READ_CLAUSE_VARIABLE_NAMES), \
|
||||||
PAR("variables", filler, READ_CLAUSE_VARIABLES), \
|
PAR("variables", filler, READ_CLAUSE_VARIABLES), \
|
||||||
PAR("term_position", filler, READ_CLAUSE_TERM_POSITION), \
|
PAR("term_position", filler, READ_CLAUSE_TERM_POSITION), \
|
||||||
@ -1208,12 +1208,12 @@ static Int read2(
|
|||||||
|
|
||||||
/** @pred read(- _T_) is iso
|
/** @pred read(- _T_) is iso
|
||||||
|
|
||||||
Reads the next term from the current input stream, and unifies it with
|
Reads the next term from the current input stream, and unifies it with
|
||||||
_T_. The term must be followed by a dot (`.`) and any blank-character
|
_T_. The term must be followed by a dot (`.`) and any blank-character
|
||||||
as previously defined. The syntax of the term must match the current
|
as previously defined. The syntax of the term must match the current
|
||||||
declarations for operators (see op). If the end-of-stream is reached,
|
declarations for operators (see op). If the end-of-stream is reached,
|
||||||
_T_ is unified with the atom `end_of_file`. Further reads from of
|
_T_ is unified with the atom `end_of_file`. Further reads from of
|
||||||
the same stream may cause an error failure (see open/3).
|
the same stream may cause an error failure (see open/3).
|
||||||
|
|
||||||
*/
|
*/
|
||||||
static Int read1(
|
static Int read1(
|
||||||
@ -1224,8 +1224,8 @@ static Int read1(
|
|||||||
|
|
||||||
/** @pred fileerrors
|
/** @pred fileerrors
|
||||||
|
|
||||||
Switches on the file_errors flag so that in certain error conditions
|
Switches on the file_errors flag so that in certain error conditions
|
||||||
Input/Output predicates will produce an appropriated message and abort.
|
Input/Output predicates will produce an appropriated message and abort.
|
||||||
|
|
||||||
*/
|
*/
|
||||||
static Int fileerrors(USES_REGS1) {
|
static Int fileerrors(USES_REGS1) {
|
||||||
@ -1296,6 +1296,13 @@ X_API Term Yap_StringToTerm(const char *s, size_t len, encoding_t *encp,
|
|||||||
Term bvar = MkVarTerm(), ctl;
|
Term bvar = MkVarTerm(), ctl;
|
||||||
yhandle_t sl;
|
yhandle_t sl;
|
||||||
|
|
||||||
|
if (len == 0) {
|
||||||
|
Term rval = TermEof;
|
||||||
|
if (rval && bindings) {
|
||||||
|
*bindings = TermNil;
|
||||||
|
}
|
||||||
|
return rval;
|
||||||
|
}
|
||||||
if (bindings) {
|
if (bindings) {
|
||||||
ctl = Yap_MkApplTerm(Yap_MkFunctor(AtomVariableNames, 1), 1, &bvar);
|
ctl = Yap_MkApplTerm(Yap_MkFunctor(AtomVariableNames, 1), 1, &bvar);
|
||||||
sl = Yap_PushHandle(bvar);
|
sl = Yap_PushHandle(bvar);
|
||||||
@ -1363,7 +1370,7 @@ Term Yap_AtomToTerm(Atom a, Term opts) {
|
|||||||
}
|
}
|
||||||
|
|
||||||
rval = Yap_read_term(sno, opts, 3);
|
rval = Yap_read_term(sno, opts, 3);
|
||||||
Yap_CloseStream(sno);
|
Yap_CloseStream(sno);
|
||||||
return rval;
|
return rval;
|
||||||
}
|
}
|
||||||
|
|
||||||
|
30
pl/debug.yap
30
pl/debug.yap
@ -276,6 +276,36 @@ be lost.
|
|||||||
'$debugger_input',
|
'$debugger_input',
|
||||||
'$do_spy'(G, Mod, CP, spy).
|
'$do_spy'(G, Mod, CP, spy).
|
||||||
|
|
||||||
|
'$spy'([Mod|G], A1) :-
|
||||||
|
G =.. L,
|
||||||
|
lists:append( L, [A1], NL),
|
||||||
|
NG =.. NL,
|
||||||
|
'$spy'([Mod|NG]).
|
||||||
|
|
||||||
|
'$spy'([Mod|G], A1, A2) :-
|
||||||
|
G =.. L,
|
||||||
|
lists:append( L, [A1, A2], NL),
|
||||||
|
NG =.. NL,
|
||||||
|
'$spy'([Mod|NG]).
|
||||||
|
|
||||||
|
'$spy'([Mod|G], A1, A2, A3) :-
|
||||||
|
G =.. L,
|
||||||
|
lists:append( L, [A1, A2, A3], NL),
|
||||||
|
NG =.. NL,
|
||||||
|
'$spy'([Mod|NG]).
|
||||||
|
|
||||||
|
'$spy'([Mod|G], A1, A2, A3, A4) :-
|
||||||
|
G =.. L,
|
||||||
|
lists:append( L, [A1, A2, A3, A4], NL),
|
||||||
|
NG =.. NL,
|
||||||
|
'$spy'([Mod|NG]).
|
||||||
|
|
||||||
|
'$spy'([Mod|G], A1, A2, A3, A4, A5) :-
|
||||||
|
G =.. L,
|
||||||
|
lists:append( L, [A1, A2, A3, A4, A5], NL),
|
||||||
|
NG =.. NL,
|
||||||
|
'$spy'([Mod|NG]).
|
||||||
|
|
||||||
/**
|
/**
|
||||||
* @pred debugger_input.
|
* @pred debugger_input.
|
||||||
* name of stream used for debugging,
|
* name of stream used for debugging,
|
||||||
|
Reference in New Issue
Block a user