Skip to content

Commit 04a928f

Browse files
committed
bstkreqd to before starting exec chain; allow for changes in locale from non-name execution; remove sf from jtexec1
1 parent 7df5d65 commit 04a928f

File tree

9 files changed

+44
-35
lines changed

9 files changed

+44
-35
lines changed

jsrc/ct.c

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -389,7 +389,6 @@ static void *jtthreadmain(void *arg){J jt=arg;I dummy;
389389
__atomic_store_n(&jt->cstackmin,jt->cstackinit-(CSTACKSIZE-CSTACKRESERVE),__ATOMIC_RELEASE); // use a local as a surrogate for the stack pointer
390390
// Note: we use cstackmin as an indication that this thread is ready to use.
391391
JOBQ *jobq=&(*JT(jt,jobqueue))[jt->threadpoolno]; // The jobq block for the threadpool we are in - never changes
392-
jt->uflags.bstkreqd=1; // init so that every top-level change of locale is reflected in startcounts. That way we can decr the global locale at end-of-job
393392

394393
// loop forever executing tasks. First time through, the thread-creation code holds the job lock until the initialization finishes
395394
nexttask: ;
@@ -473,7 +472,8 @@ nexttasklocked: ; // come here if already holding the lock, and job is set
473472
jt->locsyms=(A)(*JT(jt,emptylocale))[THREADID(jt)]; SYMSETGLOBAL(jt->locsyms,startloc); RESETRANK; jt->currslistx=-1; jt->recurstate=RECSTATERUNNING; // init what needs initing. Notably clear the local symbols
474473
jtsettaskrunning(jt); // go to RUNNING state, perhaps after waiting for system lock to finish
475474
// run the task, raising & lowering the locale execct. Bivalent
476-
if(likely(startloc!=0)){INCREXECCT(startloc); fa(startloc);} // raise execcount of current locale to protect it while running; remove the protection installed in taskrun()
475+
// obsolete if(likely(startloc!=0)){INCREXECCTIF(startloc); fa(startloc);} // raise execcount of current locale to protect it while running; remove the protection installed in taskrun()
476+
jt->uflags.bstkreqd=1; INCREXECCTIF(startloc); fa(startloc); // start new exec chain; raise execcount of current locale to protect it while running; remove the protection installed in taskrun()
477477
A arg1=job->user.args[0],arg2=job->user.args[1],arg3=job->user.args[2];
478478
fa(UNvoidAV1(job)); // job is no longer needed
479479
I dyad=!(AT(arg2)&VERB); A self=dyad?arg3:arg2; arg3=dyad?arg3:0; // the call is either noun self x or noun noun self. See which and select self. Set arg3 to 0 if monad.
@@ -484,7 +484,7 @@ nexttasklocked: ; // come here if already holding the lock, and job is set
484484
A z=(FAV(uarg3)->valencefns[dyad])(jt,arg1,uarg2,uarg3); // execute the u in u t. v
485485
// ***** return from user task and look for next one *****
486486
// obsolete if(likely(jt->global!=0))
487-
DECREXECCT(jt->global); // remove exec-protection from finishing locale. This may result in its deletion
487+
DECREXECCTIF(jt->global); // remove exec-protection from finishing exec chain. This may result in its deletion
488488
// put the result into the result block. If there was an error, use the error code as the result. But make sure the value is non0 so the pyx doesn't wait forever
489489
C errcode=0;
490490
if(unlikely(z==0)){fail:errcode=jt->jerr; errcode=(errcode==0)?EVSYSTEM:errcode;}else{realizeifvirtualERR(z,goto fail;);} // realize virtual result before returning it

jsrc/i.c

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -183,8 +183,8 @@ static B jtconsinitt(J jt){
183183
jt->cct= 1.0-FUZZ;
184184
jt->xmode=XMEXACT;
185185
// create an initial stack, so that stack[-1] can be used for saving error messages
186-
jt->parserstackframe.parserstkbgn=jt->parserstackframe.parserstkend1=&jt->initparserstack[1]; // ensure valid error stack after final return
187-
jt->uflags.bstkreqd=1; // indicate that cocurrent has been called at this level. This forces unquote to incr/decr execcts for every cocurrent, leaving only one active at final return
186+
jt->parserstackframe.parserstkbgn=jt->parserstackframe.parserstkend1=&jt->initparserstack[1]; // ensure valid error stack after final return (start off the end)
187+
// obsolete jt->uflags.bstkreqd=1; // indicate that cocurrent has been called at this level. This forces unquote to incr/decr execcts for every cocurrent, leaving only one active at final return
188188
R 1;
189189
}
190190

jsrc/io.c

Lines changed: 13 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -443,23 +443,22 @@ F1(jtjoff){I x;
443443
R 0;
444444
}
445445

446-
// wrapper to raise the execct of the starting locale while an immex is running
447-
// If the global locale changes during execution, we must have called cocurrent or 18!:4 directly. If cocurrent, there will be a
448-
// POPFIRST on the stack (which is otherwise empty). If there is a POPFIRST we need to decrement the current global locale.
449-
// in this routine jt is a thread pointer and jjt is the shared pointer
446+
// wrapper to put a new exec chain into play
447+
// set bstkreqd, incr the starting locale, decr the final locale. unquote will EXECCTIF all changes
450448
static void jtimmexexecct(JJ jt, A x){
451-
A startloc=jt->global; // point to current global locale
452-
INCREXECCT(startloc); // raise usecount of current locale to protect it while running
453-
jtimmex(jt,x); // run the sentence
454-
DECREXECCT(startloc); // remove protection from executed locale. This may result in its deletion
449+
// obsolete A startloc=jt->global; // point to current global locale
450+
// obsolete INCREXECCT(startloc); // raise usecount of current locale to protect it while running
451+
// obsolete jtimmex(jt,x); // run the sentence
452+
// obsolete DECREXECCT(startloc); // remove protection from executed locale. This may result in its deletion
453+
jt->uflags.bstkreqd=1; INCREXECCTIF(jt->global); jtimmex(jt,x); DECREXECCTIF(jt->global); // execution of the sentence may change jt->global
455454
}
456455

457456

458457
// if there is an immex sentence, fetch it, protect it from deletion, run it, and undo the protection
459458
// in this routine jt is a thread pointer and jjt is the shared pointer
460459
static void runiep(JS jjt,JJ jt,A *old){
461460
while(1){
462-
// if there is an immex phrase, protect it during its execution
461+
// if there is an immex phrase, protect it during its execution
463462
A iep=0; if(jt->iepdo&1){READLOCK(jjt->felock) if((iep=jjt->iep)!=0)ra(iep); READUNLOCK(jjt->felock)}
464463
if(iep==0)break;
465464
// run the IEP and clean up after. We leave iepdo set to 'running' during the exec to suppress postmortem debugging while IEPs are about
@@ -487,7 +486,7 @@ static I jdo(JS jt, C* lp){I e;A x;JJ jm=MDTHREAD(jt); // get address of thread
487486
// user wants to debug the error. Transfer the pmstack to the debug stack in reverse order. ra() the self for each block - necessary in case they are reassigned while on the stack
488487
DC s=jm->pmstacktop, sp=0; while(s){DC sn=s->dclnk; s->dclnk=sp; if(s->dctype==DCCALL&&s->dcpflags==1)ra(s->dcf) sp=s; s=sn;} jm->sitop=sp; jm->pmstacktop=0; // reverse pmstack, move it to debug stack
489488
if(sp)sp->dcsusp=1; // debug discards lines before the suspension, so we have to mark the stack-top as starting suspension
490-
lp="'Use y___1 to look inside top stack frame; see code.jsoftware.com/wiki/Debug/Stack#irefs' [ dbg_z_ 513"; // change the sentence to one that starts the debug window with no TRACEDBSUSCLEAR flag
489+
lp="'dbr 0 to end inspection; use y___1 to look inside top stack frame (see code.jsoftware.com/wiki/Debug/Stack#irefs)' [ dbg_z_ 513"; // change the sentence to one that starts the debug window with no TRACEDBSUSCLEAR flag
491490
}
492491
}
493492

@@ -514,10 +513,13 @@ static I jdo(JS jt, C* lp){I e;A x;JJ jm=MDTHREAD(jt); // get address of thread
514513
e=jm->jerr; MODESRESET(jm) // save error on sentence to be our return code
515514
jtshowerr(jm); // jt flags=0 to force typeout of iep errors
516515
RESETERRT(jm)
517-
// if there is an immex latent expression (9!:27), execute it before prompting
516+
// if there is an immex latent expression (9!:27), execute it before prompting. It runs in the same state as the user sentence
518517
// All these immexes run with result-display enabled (jt flags=0)
519518
// BUT: don't do it if the call is recursive. The user might have set the iep before a prompt, and won't expect it to be executed asynchronously
519+
// we could do this in a loop back through exexct, but we choose not to
520520
if(likely(!(jm->recurstate&RECSTATERENT)))runiep(jt,jm,old); // IEP does not display its errors
521+
522+
// user's sentence and iep if any are finished. e has the return code. Return to user
521523
if(likely(wasidle)){ // returning to immex in the FE
522524
jtclrtaskrunning(jm); // clear running state in case other tasks are running and need system lock - but not if recursion
523525
// since we are returning to user-prompt level, we might as well take user think time to trim up memory

jsrc/jt.h

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -99,10 +99,11 @@ struct __attribute__((aligned(JTFLAGMSK+1))) JTTstruct {
9999
// debug flags are also used for dbuser
100100
// ************************************** here starts the area that is initialized to 0 when task starts 0x14
101101
C init0area[0]; // label for initializing. We overcopy to a full I, then back up to copy 0
102-
C bstkreqd; // init to 1 at thread startup. cleared at the start of each function call. Set at the end of a function call if (1) the function was cocurrent or (2) bstkreqd was set just before the function was called. Taken together, these conditions
103-
// mean that bstkreqd is set at the end of a function af that function or any preceding functions with the same caller changed the implied locale. When a function ends, it looks at bstkreqd. If it is set,
104-
// the running locale has been changed by a called function and must be reset. bstkreqd is set to 1 initially, which causes each change of locale before the first named call to incr/decr both locale counts, thus
105-
// housekeeping the counts as if there were a named call to begin with.
102+
C bstkreqd; // cleared at the start of each function call. Set at the end of a function call if (1) the function was cocurrent or (2) bstkreqd was set just before the function was called. Taken together, these conditions
103+
// mean that bstkreqd is set at the end of a function if that function or any preceding functions with the same caller changed the implied locale. When a function ends, it looks at bstkreqd. If it is set,
104+
// the running locale has been changed by a called function and must be reset. When a name is called, bstkreqd means that a previous name called by the same caller changes the locale.
105+
// this is important because the FIRST change of locale skips some processing. When starting an execution, such as from the console or in a thread: set bstkreqd to 1, INCREXECCTIF the starting thread, DECREXECCTIF at end of exec.
106+
// This will guarantee raising the usecount of each executing thread
106107
union {
107108
US spflag; // access as short
108109
struct {

jsrc/jtype.h

Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -875,6 +875,9 @@ typedef DST* DC;
875875
#define DECREXECCT(l) if(--LXAV0(l)[SYMLEXECCT]==0)locdestroy(l);
876876
#define DELEXECCT(l) if((LXAV0(l)[SYMLEXECCT]&=~EXECCTNOTDELD)==0)locdestroy(l);
877877
#endif
878+
#define INCREXECCTIF(l) {if(unlikely(!(LXAV0(l)[SYMLEXECCT]&EXECCTPERM)))INCREXECCT(l)}
879+
#define DECREXECCTIF(l) {if(unlikely(!(LXAV0(l)[SYMLEXECCT]&EXECCTPERM)))DECREXECCT(l)}
880+
#define DELEXECCTIF(l) {if(likely(!(LXAV0(l)[SYMLEXECCT]&EXECCTPERM)))DELEXECCT(l)}
878881

879882
typedef struct {
880883
A name; // name on lhs of assignment; in LINFO, pointer to NM block. May be 0 in zombie values (modified cached values)

jsrc/px.c

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,9 +32,9 @@ DF1(jtexec1){A z;
3232
if(AT(w)&NAME){z=nameref(w,jt->locsyms); // the case ".@'name' which is the fastest way to refer to a deferred name
3333
}else{
3434
F1RANK(1,jtexec1,self);
35-
A savself = jt->parserstackframe.sf; // in case we are in a recursion, preserve the restart point
35+
// obsolete A savself = jt->parserstackframe.sf; // in case we are in a recursion, preserve the restart point
3636
STACKCHKOFL z=PARSERVALUE(parseforexec(ddtokens(vs(w),4+1+!!EXPLICITRUNNING))); // replace DDs, but require that they be complete within the string (no jgets)
37-
jt->parserstackframe.sf=savself;
37+
// obsolete jt->parserstackframe.sf=savself;
3838
}
3939
RETF(z&&!(AT(z)&NOUN)?mtv:z); // if non-noun result, return empty $0
4040
}

jsrc/sc.c

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -223,23 +223,23 @@ DF2(jtunquote){A z;
223223
exitpop: ;
224224
// LSB of z is set in the return iff what we just called was cocurrent
225225
// jt->global here is always the same as before the call
226-
if(unlikely(((C)(I)z|jt->uflags.bstkreqd)&1)){ // cocurrent OR return after cocurrent?
226+
if(unlikely(((C)(I)z|jt->uflags.bstkreqd)&1)){ // cocurrent OR return after some earlier cocurrent?
227227
if((C)(I)z&1){ // was successful call to cocurrent?
228228
// here the name we called was cocurrent, possibly through a locative. This is where we change jt->global in the caller
229229
// The incr/decrs here are on behalf of the caller of cocurrent. We always incr the locale we move to; we decr a locale
230230
// only if a previous cocurrent moved to it; the first time we don't know whether it was incrd, and we leave
231231
// the decr to the caller of cocurrent
232-
z=(A)((I)z&~1); INCREXECCT(z); // z has the locale to switch to. clear flag bit; indicate new execution starting in the locale we switch to
232+
z=(A)((I)z&~1); INCREXECCTIF(z); // z has the locale to switch to. clear flag bit; indicate new execution starting in the locale we switch to
233233
// we temporarily started an execution for the locative (now jt->global). We will close that below in common code
234-
if(flgd0cpC&FLGLOCCHANGED)DECREXECCT(stack.global) // if the caller's locale was moved to by cocurrent (i.e. this is the second cocurrent in the calling function), it must be replaced by z. No DECR is performed for the FIRST cocurrent, so if that was entered by a locative
234+
if(flgd0cpC&FLGLOCCHANGED)DECREXECCTIF(stack.global) // if the caller's locale was moved to by cocurrent (i.e. this is the second+ cocurrent in the calling function), it must be replaced by z. No DECR is performed for the FIRST cocurrent, so if that was entered by a locative
235235
// it will be owed a DECR. We can't DECR the first call because it might be in execution higher in the stack and already have a delete outstanding
236236
SYMSETGLOBALINLOCAL(jt->locsyms,z); // install new globals pointer into the locsyms (if any)...
237237
stack.global=z; // ... and into the area we will pop from, thus storing through to the caller
238238
z=mtm; // we have switched; this will be the result of cocurrent
239239
flgd0cpC|=FLGLOCCHANGED; // leave bstkreqd set as a flag indicating next function's caller has encountered cocurrent
240-
}else if(jt->uflags.bstkreqd)DECREXECCT(jt->global) // if we started with a locative and then had cocurrent, we must close the final change of locale
240+
}else if(jt->uflags.bstkreqd)DECREXECCTIF(jt->global) // we are returning from this function, which called cocurrent. Close the final change of locale
241241
}
242-
jt->uflags.bstkreqd=(C)(flgd0cpC>>FLGLOCCHANGEDX); // bstkreqd is set after the return if the CALLER OF THE EXITING ROUTINE has seen cocurrent. This was passed into the exiting routine as FLGLOCCHANGED. bstkreqd is set to be used either by the next call of the return from this caller
242+
jt->uflags.bstkreqd=(C)(flgd0cpC>>FLGLOCCHANGEDX); // bstkreqd is set after the return if the CALLER OF THE EXITING ROUTINE has seen cocurrent. This was passed into the exiting routine as FLGLOCCHANGED. bstkreqd is set to be used by either the next call or the return from this caller
243243
if(unlikely(flgd0cpC&FLGLOCINCRDECR))DECREXECCT(explocale) // If we used a locative, undo its incr. If there were cocurrents, the incr was a while back
244244
// ************** errors OK now
245245
exitfa:

jsrc/sl.c

Lines changed: 9 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -192,7 +192,7 @@ A jtindexnl(J jt,I n) {A z=(A)IAV1(JT(jt,stnum))[n]; R z&&LOCPATH(z)?z:0; } //
192192
// For k=0 or 1, we have made sure there are 2-k symbols reserved (for the assignments we make). Not required for k=2, which is not assigned
193193
A jtstcreate(J jt,C k,I p,I n,C*u){A g,x,xx;L*v;
194194
// allocate the symbol table itself: we have to give exactly what the user asked for so that cloned tables will hash identically; but a minimum of 1 chain field so hashes can always run
195-
GATV0(g,SYMB,MAX(p,SYMLINFOSIZE+1),0); AFLAGORLOCAL(g,SYMB) LXAV0(g)[SYMLEXECCT]=EXECCTNOTDELD; // All SYMB tables are born recursive. Init EXECCT to 'in use'
195+
GATV0(g,SYMB,MAX(p,SYMLINFOSIZE+1),0); AFLAGORLOCAL(g,SYMB) // All SYMB tables are born recursive.
196196
// Allocate a symbol for the locale info, install in special hashchain 0. Set flag;
197197
// (it is queried by 18!:_2)
198198
// The allocation clears all the hash chain bases, including the one used for SYMLINFO
@@ -216,7 +216,7 @@ A jtstcreate(J jt,C k,I p,I n,C*u){A g,x,xx;L*v;
216216
LOCBLOOM(g)=0; // Init Bloom filter to 'nothing assigned'
217217
ACINITZAP(x); ACINIT(x,ACUC2) // now that we know we will succeed, transfer ownership to name to the locale and stloc, one each
218218
AR(g)=ARNAMED; // set rank to indicate named locale
219-
LXAV0(g)[SYMLEXECCT]=EXECCTPERM; // mark all named locales permanent
219+
LXAV0(g)[SYMLEXECCT]=EXECCTPERM+EXECCTNOTDELD; // mark all named locales permanent
220220
break;
221221
case 1: // numbered locale - we have no lock
222222
AR(g)=ARINVALID; // until the table is all filled in, it is in an invalid state and cannot be inspected when freed
@@ -233,11 +233,13 @@ A jtstcreate(J jt,C k,I p,I n,C*u){A g,x,xx;L*v;
233233
LOCNAME(g)=x; // set name pointer in SYMLINFO
234234
ACINITZAP(x); // now that we know we will succeed, transfer ownership to name to the locale
235235
AR(g)=0; // set rank to indicate numbered locale
236+
LXAV0(g)[SYMLEXECCT]=EXECCTNOTDELD; // numbered locales are nondeleted but not permanent
236237
break;
237238
case 2: // local symbol table - we have no lock and we don't assign
238239
AR(g)=ARLOCALTABLE; // flag this as a local table so the first hashchain is not freed
239240
// The first hashchain is not used as a symbol pointer - it holds xy bucket info
240241
// Bloom filter not used for local symbol tables (the field is a chain for the stack of active defs)
242+
// local symbol tables don't have execcts
241243
break;
242244
}
243245
R g;
@@ -316,7 +318,8 @@ A jtstfind(J jt,I n,C*u,I bucketx){
316318

317319

318320
// Bring a destroyed locale back to life as if it were newly created: clear the chains, set the default path, clear the Bloom filter
319-
#define REINITZOMBLOC(g) mvc((AN(g)-SYMLINFOSIZE)*sizeof(LXAV0(g)[0]),LXAV0(g)+SYMLINFOSIZE,1,MEMSET00); LOCBLOOM(g)=0; LXAV0(g)[SYMLEXECCT]=EXECCTNOTDELD; LOCPATH(g)=JT(jt,zpath);
321+
// this happens only if we force-deleted a permanent localce, so retore it to permanent
322+
#define REINITZOMBLOC(g) mvc((AN(g)-SYMLINFOSIZE)*sizeof(LXAV0(g)[0]),LXAV0(g)+SYMLINFOSIZE,1,MEMSET00); LOCBLOOM(g)=0; LXAV0(g)[SYMLEXECCT]=EXECCTPERM+EXECCTNOTDELD; LOCPATH(g)=JT(jt,zpath);
320323
// we should check whether the path in non0 but that would only matter if two threads created the locale simultaneously AND set a path, and the only loss would be that the path would leak
321324
static F2(jtloccre);
322325

@@ -653,7 +656,7 @@ F1(jtsetpermanent){A g;
653656
/* check for redefinition (erasure) of entire symbol table. */
654657

655658
// 18!:55 destroy locale(s) from user's point of view. This counts as one usecount; others are in execution and in paths. When all go to 0, delete the locale
656-
// if x is 271828, do the
659+
// if x is 271828, do the deletion even if on a permanent locale
657660
F2(jtlocexmark){A g,*wv,y,z;B *zv;C*u;I i,m,n;
658661
if(unlikely(AT(w)&NOUN)){ // dyadic call
659662
I x; x=i0(a); if(jt->jerr){RESETERR; ASSERT(0,EVVALENCE)} ASSERT(x==271828,EVVALENCE) // if not 271828, valence error
@@ -681,8 +684,8 @@ F2(jtlocexmark){A g,*wv,y,z;B *zv;C*u;I i,m,n;
681684
}
682685
if(g){I k; // if the specified locale exists in the system...
683686
if(a){ASSERTSUFF(*JT(jt,zpath)!=g,EVRO,z=0; goto exitlock;) LXAV0(g)[SYMLEXECCT]=0; locdestroy(g); // forced delete, clear execct/del ct & do it
684-
// ignore the deletion if the locale is PERMANENT. The execct is unreliable then
685-
}else if(!(AC(g)&ACPERMANENT))DELEXECCT(g) // say that the user doesn't want this locale any more. Paths, execs, etc. still might.
687+
// ignore the deletion if the locale is execct-permanent. The execct is unreliable then
688+
}else DELEXECCTIF(g) // say that the user doesn't want this locale any more. Paths, execs, etc. still might.
686689
}
687690
}
688691
exitlock:

test/glocale.ijs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -231,7 +231,7 @@ f =: 0&".&.> y =: 18!:3 ''
231231
(i.0 0) -: (i.0) lpath <'asdf'
232232
(i.0 0) -: (0$a:)lpath <'asdf'
233233

234-
18!:55 ;:'a abc asdf bc cool d first new NonExistent NonExistentLocale'
234+
(271828) 18!:55 ;:'a abc asdf bc cool d first new NonExistent NonExistentLocale'
235235
18!:55 e
236236
18!:55 >f
237237

@@ -241,7 +241,7 @@ after =. 00 + 00
241241
before =. 7!:0 ''
242242
1: 18!:3 <'a'
243243
('a';'a';'a';'a';'a';'a';'a';'a';'a';'a';'a') 18!:2 <'a'
244-
18!:55 <'a'
244+
(271828) 18!:55 <'a'
245245
after =. 7!:0 ''
246246
64 >: after - before
247247

0 commit comments

Comments
 (0)