Skip to content

Commit

Permalink
CLEANUP: PL_new_term_refs() now takes size_t argument (was int).
Browse files Browse the repository at this point in the history
  • Loading branch information
JanWielemaker committed Nov 1, 2023
1 parent 3e4f02c commit 0a8722a
Show file tree
Hide file tree
Showing 9 changed files with 33 additions and 19 deletions.
2 changes: 1 addition & 1 deletion src/SWI-Prolog.h
Original file line number Diff line number Diff line change
Expand Up @@ -480,7 +480,7 @@ PL_EXPORT(int) PL_assert(term_t term, module_t m, int flags);
*******************************/

/* Creating and destroying term-refs */
PL_EXPORT(term_t) PL_new_term_refs(int n);
PL_EXPORT(term_t) PL_new_term_refs(size_t n);
PL_EXPORT(term_t) PL_new_term_ref(void);
PL_EXPORT(term_t) PL_copy_term_ref(term_t from);
PL_EXPORT(void) PL_reset_term_refs(term_t r);
Expand Down
6 changes: 3 additions & 3 deletions src/pl-fli.c
Original file line number Diff line number Diff line change
Expand Up @@ -334,10 +334,10 @@ bArgVar(DECL_LD Word ap, Word vp)
*******************************/

term_t
PL_new_term_refs(DECL_LD int n)
PL_new_term_refs(DECL_LD size_t n)
{ Word t;
term_t r;
int i;
size_t i;
FliFrame fr;

if ( !ensureLocalSpace(n*sizeof(word)) )
Expand Down Expand Up @@ -404,7 +404,7 @@ PL_new_term_ref_noshift(DECL_LD)


API_STUB(term_t)
(PL_new_term_refs)(int n)
(PL_new_term_refs)(size_t n)
( if ( (void*)fli_context <= (void*)environment_frame )
fatalError("PL_new_term_refs(): No foreign environment");

Expand Down
2 changes: 1 addition & 1 deletion src/pl-fli.h
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,7 @@ void popTermRef(void);
int _PL_get_arg(size_t index, term_t t, term_t a);
term_t PL_new_term_ref(void);
term_t PL_new_term_ref_noshift(void);
term_t PL_new_term_refs(int n);
term_t PL_new_term_refs(size_t n);
functor_t PL_new_functor_sz(atom_t f, size_t arity);
int globalizeTermRef(term_t t);
void PL_reset_term_refs(term_t r);
Expand Down
8 changes: 4 additions & 4 deletions src/pl-gc.c
Original file line number Diff line number Diff line change
Expand Up @@ -1026,7 +1026,7 @@ mark_term_refs()
Sdprintf("Marking foreign frame %ld (size=%d)\n",
(Word)fr-(Word)lBase, n));

assert(fr->magic == FLI_MAGIC);
FLI_ASSERT_VALID(fr);
for( ; n-- > 0; sp++ )
{ if ( !is_marked(sp) )
{ if ( isGlobalRef(*sp) )
Expand Down Expand Up @@ -1661,7 +1661,7 @@ early_reset_vars(DECL_LD mark *m, Word top, GCTrailEntry te)
#define mark_foreign_frame(fr, te) LDFUNC(mark_foreign_frame, fr, te)
static GCTrailEntry
mark_foreign_frame(DECL_LD FliFrame fr, GCTrailEntry te)
{ DEBUG(CHK_SECURE, assert(fr->magic == FLI_MAGIC));
{ FLI_ASSERT_VALID(fr);

if ( isRealMark(fr->mark) )
{ te = early_reset_vars(&fr->mark, (Word)fr, te);
Expand Down Expand Up @@ -2972,7 +2972,7 @@ sweep_foreign()
{ Word sp = refFliP(fr, 0);
int n = fr->size;

DEBUG(CHK_SECURE, assert(fr->magic == FLI_MAGIC));
FLI_ASSERT_VALID(fr);

if ( isRealMark(fr->mark) )
sweep_mark(&fr->mark);
Expand Down Expand Up @@ -4077,7 +4077,7 @@ check_foreign(void)
{ Word sp = refFliP(ff, 0);
int n = ff->size;

assert(ff->magic == FLI_MAGIC);
FLI_ASSERT_VALID(ff);
if ( ff->parent )
{ assert(ff->parent < ff);
assert(onStack(local, ff->parent));
Expand Down
18 changes: 16 additions & 2 deletions src/pl-incl.h
Original file line number Diff line number Diff line change
Expand Up @@ -1824,10 +1824,24 @@ struct queryFrame

#define FLI_MAGIC 82649821
#define FLI_MAGIC_CLOSED 42424242
#ifdef O_DEBUG
#define FLI_SET_VALID(fr) ((fr)->magic = FLI_MAGIC)
#define FLI_SET_CLOSED(fr) ((fr)->magic = FLI_MAGIC_CLOSED)
#define FLI_VALID(fr) ((fr)->magic == FLI_MAGIC)
#define FLI_ASSERT_VALID(fr) assert(FLI_VALID(fr))
#else
#define FLI_SET_VALID(fr) (void)0
#define FLI_SET_CLOSED(fr) (void)0
#define FLI_VALID(fr) (1)
#define FLI_ASSERT_VALID(fr) (void)0
#endif

struct fliFrame
{ int magic; /* Magic code */
int size; /* # slots on it */
{
#ifdef O_DEBUG
int magic; /* Magic code */
#endif
size_t size; /* # slots on it */
FliFrame parent; /* parent FLI frame */
mark mark; /* data-stack mark */
};
Expand Down
2 changes: 1 addition & 1 deletion src/pl-prims.c
Original file line number Diff line number Diff line change
Expand Up @@ -2098,7 +2098,7 @@ PRED_IMPL("?=", 2, can_compare, 0)
if ( rc )
{ FliFrame fr = (FliFrame) valTermRef(fid);

assert(fr->magic == FLI_MAGIC);
FLI_ASSERT_VALID(fr);
if ( fr->mark.trailtop != tTop )
rc = FALSE;
} else if ( exception_term )
Expand Down
4 changes: 2 additions & 2 deletions src/pl-vmi.c
Original file line number Diff line number Diff line change
Expand Up @@ -4632,7 +4632,7 @@ VMI(I_FOPEN, 0, 0, ())
ffr->size = 0;
NoMark(ffr->mark);
ffr->parent = fli_context;
ffr->magic = FLI_MAGIC;
FLI_SET_VALID(ffr);
fli_context = ffr;
FFR_ID = consTermRef(ffr);
SAVE_REGISTERS(QID);
Expand Down Expand Up @@ -4811,7 +4811,7 @@ VMH(foreign_redo, 0, (), ())
ffr->size = 0;
NoMark(ffr->mark);
ffr->parent = fli_context;
ffr->magic = FLI_MAGIC;
FLI_SET_VALID(ffr);
fli_context = ffr;
FFR_ID = consTermRef(ffr);
SAVE_REGISTERS(QID);
Expand Down
8 changes: 4 additions & 4 deletions src/pl-wam.c
Original file line number Diff line number Diff line change
Expand Up @@ -320,7 +320,7 @@ open_foreign_frame(DECL_LD)
Mark(fr->mark);
DEBUG(CHK_SECURE, assert(fr>fli_context));
fr->parent = fli_context;
fr->magic = FLI_MAGIC;
FLI_SET_VALID(fr);
fli_context = fr;

return consTermRef(fr);
Expand All @@ -331,10 +331,10 @@ void
PL_close_foreign_frame(DECL_LD fid_t id)
{ FliFrame fr = (FliFrame) valTermRef(id);

if ( !id || fr->magic != FLI_MAGIC )
if ( !id || !FLI_VALID(fr) )
sysError("PL_close_foreign_frame(): illegal frame: %d", id);
DiscardMark(fr->mark);
fr->magic = FLI_MAGIC_CLOSED;
FLI_SET_CLOSED(fr);
fli_context = fr->parent;
lTop = (LocalFrame) fr;
}
Expand Down Expand Up @@ -383,7 +383,7 @@ PL_open_signal_foreign_frame(int sync)
}

fr = addPointer(lTop, margin);
fr->magic = FLI_MAGIC;
FLI_SET_VALID(fr);
fr->size = 0;
Mark(fr->mark);
fr->parent = fli_context;
Expand Down
2 changes: 1 addition & 1 deletion src/pl-write.c
Original file line number Diff line number Diff line change
Expand Up @@ -191,7 +191,7 @@ writeNumberVar(DECL_LD term_t t, write_options *options)
if ( LD->var_names.numbervars_frame )
{ FliFrame fr = (FliFrame)valTermRef(LD->var_names.numbervars_frame);

assert(fr->magic == FLI_MAGIC);
FLI_ASSERT_VALID(fr);
if ( false(options, PL_WRT_NUMBERVARS) &&
fr->mark.globaltop > (Word)f )
return FALSE; /* older $VAR term */
Expand Down

0 comments on commit 0a8722a

Please sign in to comment.