remove YAP memory (string) streams.

This commit is contained in:
Vitor Santos Costa
2011-02-12 18:42:44 +00:00
parent be79c3326e
commit 2d07a7730e
15 changed files with 333 additions and 738 deletions

View File

@@ -32,86 +32,69 @@
term_to_atom/2
]).
:- use_module(library(memfile)).
:- meta_predicate(with_output_to_chars(0,?)).
:- meta_predicate(with_output_to_chars(0,-,?)).
:- meta_predicate(with_output_to_chars(0,-,?,?)).
format_to_chars(Form, Args, OUT) :-
format_to_chars(Form, Args, OUT, []).
format_to_chars(Format, Args, Codes) :-
format(codes(Codes), Format, Args).
format_to_chars(Form, Args, OUT, L0) :-
open_mem_write_stream(Stream),
format(Stream,Form,Args),
peek_mem_write_stream(Stream, L0, O),
close(Stream),
O = OUT.
format_to_chars(Format, Args, OUT, L0) :-
format(codes(OUT, L0), Format, Args).
write_to_chars(Term, Codes) :-
format(codes(Codes), '~w', [Term]).
write_to_chars(Term, Out, Tail) :-
format(codes(Out,Tail),'~w',[Term]).
write_to_chars(Term, OUT) :-
write_to_chars(Term, [], OUT).
atom_to_chars(Atom, OUT) :-
atom_to_chars(Atom, [], OUT).
atom_codes(Atom, OUT).
atom_to_chars(Atom, L0, OUT) :-
var(Atom), !,
throw(error(instantiation_error,atom_to_chars(Atom, L0, OUT))).
atom_to_chars(Atom, L0, OUT) :-
atom(Atom), !,
open_mem_write_stream(Stream),
write(Stream, Atom),
peek_mem_write_stream(Stream, L0, O),
close(Stream),
O = OUT.
atom_to_chars(Atom, L0, OUT) :-
throw(error(type_error(atom,Atom),atom_to_chars(Atom, L0, OUT))).
format(codes(L0, OUT), '~a', [Atom]).
number_to_chars(Number, OUT) :-
number_to_chars(Number, [], OUT).
number_codes(Number, OUT).
number_to_chars(Number, L0, OUT) :-
var(Number), !,
throw(error(instantiation_error,number_to_chars(Number, L0, OUT))).
number_to_chars(Number, L0, OUT) :-
number(Number), !,
open_mem_write_stream(Stream),
write(Stream, Number),
peek_mem_write_stream(Stream, L0, O),
close(Stream),
O = OUT.
format(codes(L0, OUT), '~w', [Number]).
number_to_chars(Number, L0, OUT) :-
throw(error(type_error(number,Number),number_to_chars(Number, L0, OUT))).
open_chars_stream(Chars, Stream) :-
open_mem_read_stream(Chars, Stream).
open_chars_stream(Codes, Stream) :-
open_chars_stream(Codes, Stream, '').
with_output_to_chars(Goal, Chars) :-
with_output_to_chars(Goal, [], Chars).
open_chars_stream(Codes, Stream, Postfix) :-
new_memory_file(MF),
open_memory_file(MF, write, Out),
format(Out, '~s~w', [Codes, Postfix]),
close(Out),
open_memory_file(MF, read, Stream,
[ free_on_close(true)
]).
with_output_to_chars(Goal, L0, Chars) :-
with_output_to_chars(Goal, Stream, L0, Chars),
close(Stream).
with_output_to_chars(Goal, Stream, L0, Chars) :-
open_mem_write_stream(Stream),
current_output(SO),
set_output(Stream),
do_output_to_chars(Goal, Stream, L0, Chars, SO).
do_output_to_chars(Goal, Stream, L0, Chars, SO) :-
catch(Goal, Exception, handle_exception(Exception,Stream,SO)),
!,
set_output(SO),
peek_mem_write_stream(Stream, L0, Chars).
do_output_to_chars(_Goal, Stream, _L0, _Chars, SO) :-
set_output(SO),
close(Stream),
fail.
handle_exception(Exception, Stream, SO) :-
close(Stream),
current_output(SO),
throw(Exception).
with_output_to_chars(Goal, Codes) :-
with_output_to(codes(Codes), Goal).
with_output_to_chars(Goal, Codes, L0) :-
with_output_to(codes(Codes, L0), Goal).
%% with_output_to_chars(:Goal, -Stream, -Codes, ?Tail) is det.
%
% As with_output_to_chars/2, but Stream is unified with the
% temporary stream.
with_output_to_chars(Goal, Stream, Codes, Tail) :-
with_output_to(codes(Codes, Tail), with_stream(Stream, Goal)).
with_stream(Stream, Goal) :-
current_output(Stream),
call(Goal).

View File

@@ -156,18 +156,6 @@ X_API char* PL_atom_nchars(atom_t a, size_t *len) /* SAM check type */
return s;
}
X_API int
PL_chars_to_term(const char *s, term_t term) {
YAP_Term t,error;
if ( (t=YAP_ReadBuffer(s,&error))==0L ) {
Yap_PutInSlot(term, error);
return 0L;
}
Yap_PutInSlot(term,t);
return 1L;
}
/* SWI: term_t PL_copy_term_ref(term_t from)
YAP: NO EQUIVALENT */
/* SAM TO DO */
@@ -1512,7 +1500,7 @@ X_API int PL_unify_term(term_t l,...)
*pt++ = MkIntegerTerm((Int)va_arg(ap, void *));
break;
case PL_INT64:
#if SIZE_OF_LONG_INT==8
#if SIZEOF_LONG_INT==8
*pt++ = MkIntegerTerm((Int)va_arg(ap, long int));
#elif USE_GMP
{
@@ -2745,6 +2733,67 @@ Yap_swi_install(void)
YAP_UserCPredicate("ctime", SWI_ctime, 2);
}
int Yap_read_term(term_t t, IOSTREAM *st, term_t vs);
int
Yap_read_term(term_t t, IOSTREAM *st, term_t vs)
{
int sno = Yap_LookupSWIStream(st);
Term varnames, out, tpos;
if (!Yap_readTerm(sno, &out, &varnames, NULL, &tpos))
return FALSE;
if (!Yap_unify(out, Yap_GetFromSlot(t))) {
return FALSE;
}
if (!Yap_unify(vs, Yap_GetFromSlot(varnames))) {
return FALSE;
}
return TRUE;
}
Term
Yap_StringToTerm(char *s, Term *tp)
{
IOSTREAM *stream = Sopen_string(NULL, s, -1, "r");
int sno;
Term out, tpos;
if (!stream)
return FALSE;
sno = Yap_LookupSWIStream(stream);
if (sno < 0)
return FALSE;
if (!Yap_readTerm(sno, &out, NULL, tp, &tpos)) {
out = 0L;
}
Yap_CloseStream(sno);
Sclose(stream);
return out;
}
Term
Yap_TermToString(Term t, char *s, unsigned int sz, int flags)
{
int old_output_stream = Yap_c_output_stream;
IOSTREAM *stream = Sopen_string(NULL, s, sz, "w");
int sno;
if (!stream)
return FALSE;
sno = Yap_LookupSWIStream(stream);
if (sno < 0)
return 0L;
Yap_c_output_stream = sno;
Yap_StartSlots();
Yap_PlWriteToStream (t, sno, flags);
stream->bufp = '\0';
Yap_CloseSlots();
Yap_c_output_stream = old_output_stream;
return EX != NULL;
}
#ifdef _WIN32
#include <windows.h>