This commit is contained in:
Vitor Santos Costa 2016-08-18 01:36:17 -05:00
commit 670eacc823
6 changed files with 176 additions and 80 deletions

View File

@ -18,6 +18,8 @@
blank/3,
split/2,
split/3,
split/4,
split/5,
split_unquoted/3,
fields/2,
fields/3,
@ -27,6 +29,7 @@
file_filter/3,
file_select/2,
file_filter_with_initialization/5,
file_filter_with_start_end/5,
file_filter_with_initialization/5 as file_filter_with_init,
process/2
]).
@ -49,6 +52,7 @@ available by loading the
filter(+,+,2),
file_filter(+,+,2),
file_filter_with_initialization(+,+,2,+,:),
file_filter_with_start_end(+,+,2,2,2),
process(+,1).
:- use_module(library(lists),
@ -188,28 +192,73 @@ split_at_blank(SplitCodes, More) -->
split_at_blank(SplitCodes, More).
split_at_blank(SplitCodes, [[C|New]| More]) -->
[C], !,
split(SplitCodes, New, More).
split_(SplitCodes, New, More).
split_at_blank(_, []) --> [].
split(SplitCodes, [], More) -->
split_(SplitCodes, [], More) -->
[C],
{ member(C, SplitCodes) }, !,
split_at_blank(SplitCodes, More).
split(SplitCodes, [C|New], Set) -->
split_(SplitCodes, [C|New], Set) -->
[C], !,
split(SplitCodes, New, Set).
split(_, [], []) --> [].
split_(SplitCodes, New, Set).
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
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:
~~~~~{.prolog}
?- split("Hello * I \"am free\""," *",S).
?- split_quoted("Hello * I \"am free\""," *",S).
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'\\ ,C|New], More) -->
@ -402,6 +426,23 @@ file_filter_with_initialization(Inp, Out, Command, FormatString, Parameters) :-
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
*

View File

@ -17,6 +17,7 @@
checklist/2,
checknodes/2,
convlist/3,
convlist/4,
foldl/4,
foldl/5,
foldl/6,
@ -128,6 +129,7 @@ triple. See the example above.
maplist(3,+,+,-),
maplist(4,+,+,+,-),
convlist(2,+,-),
convlist(3,?,?,?),
mapnodes(2,+,-),
mapnodes_list(2,+,-),
checknodes(1,+),
@ -351,6 +353,29 @@ convlist(Pred, [Old|Olds], NewList) :-
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_)
@ -960,6 +985,29 @@ goal_expansion(convlist(Meta, ListIn, ListOut), Mod:Goal) :-
RecursiveCall)
], 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_allowed,
callable(Meta),

View File

@ -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

View File

@ -225,6 +225,7 @@ int Yap_open_buf_write_stream(encoding_t enc, memBufSource src) {
#endif
#else
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.max_size = PLGETC_BUF_SIZE - 1;
st->u.mem_string.pos = 0;

View File

@ -1296,6 +1296,13 @@ X_API Term Yap_StringToTerm(const char *s, size_t len, encoding_t *encp,
Term bvar = MkVarTerm(), ctl;
yhandle_t sl;
if (len == 0) {
Term rval = TermEof;
if (rval && bindings) {
*bindings = TermNil;
}
return rval;
}
if (bindings) {
ctl = Yap_MkApplTerm(Yap_MkFunctor(AtomVariableNames, 1), 1, &bvar);
sl = Yap_PushHandle(bvar);

View File

@ -276,6 +276,36 @@ be lost.
'$debugger_input',
'$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.
* name of stream used for debugging,