Interpreter versus StackInterpreter hierarchy

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
6 messages Options
Reply | Threaded
Open this post in threaded view
|

Interpreter versus StackInterpreter hierarchy

Ben Coman
 
The hierarchy goes
  VMClass
     InterpreterPrimitives
        StackIntepreter
          StackIntepreterPrimitives
             CoInterpreter
               CoInterpreterPrimitives

from which a tick / tock (XXInterpreter / XXInterpreterPrimitives)
pattern is apparent,
and I wonder why Interpreter is missing above InterpreterPrimitives
sitting off to the side.  I guess it is something to do with
InterpreterPrimitives composing objectMemory as an instance variable
rather than inheriting from ObjectMemory as Interpeter does?

The reason I ask is that I'm trying a new approach to the OwnedLock primitives
where if waitAcquire primitive sleeps, when the process wakes up it
retries the primitive.
So effectively the process sleeps at the top of the waitAquire rather
than the bottom,
and the process truly cannot proceed past that point until it gains
the lock. I have this working if StackInterpreterPrimitives holds the
primitive, but if I move the primitive to InterpreterPrimitives,
instructionPointer is unknown.


P.S. For the curious, here is the proof of concept I tried.  A single
call to the primitive counts up to four by backing up the
instructionPointer such that the primitive is executed again, until
the exit condition of four is reached.

(Note the use of Semaphore and ExcessSignalsIndex is not significant,
just an expedient template I was familiar with.)

# VM SIDE...

StackInterpreterPrimitives >> primitiveRetryExperiment
    | excessSignals stackTop |
    stackTop := self stackTop.
    excessSignals := objectMemory fetchInteger: ExcessSignalsIndex
ofObject: stackTop.
    excessSignals := excessSignals + 1.
    objectMemory storeInteger: ExcessSignalsIndex
        ofObject: stackTop
        withValue: excessSignals.
    [ excessSignals > 3 ] ifFalse: [ instructionPointer :=
instructionPointer - 1 ].

StackInterpreter class >> initializePrimitiveTable
    (234 primitiveRetryExperiment)


# IMAGE SIDE...

Semaphore subclass: #PrimExp
    instanceVariableNames: ''
    classVariableNames: ''
    package: '0PrimitiveRetryExperiment'

PrimExp >> initialize
    excessSignals := 1.

PrimExp >> primRetryExperiment
    <primitive: 234>

PrimExp >> excessSignals
    ^ excessSignals

# TEST CASE...

PrimExp new primRetryExperiment excessSignals
    --> 4

I've only done this with the Stack VM so far.  I'll report further
when I try it with Cog.

cheers -ben
Reply | Threaded
Open this post in threaded view
|

Re: Interpreter versus StackInterpreter hierarchy

Clément Béra
 


On Thu, May 19, 2016 at 3:42 PM, Ben Coman <[hidden email]> wrote:

The hierarchy goes
  VMClass
     InterpreterPrimitives
        StackIntepreter
          StackIntepreterPrimitives
             CoInterpreter
               CoInterpreterPrimitives

from which a tick / tock (XXInterpreter / XXInterpreterPrimitives)
pattern is apparent,
and I wonder why Interpreter is missing above InterpreterPrimitives
sitting off to the side.  I guess it is something to do with
InterpreterPrimitives composing objectMemory as an instance variable
rather than inheriting from ObjectMemory as Interpeter does?

I think this is exactly that.


The reason I ask is that I'm trying a new approach to the OwnedLock primitives
where if waitAcquire primitive sleeps, when the process wakes up it
retries the primitive.
So effectively the process sleeps at the top of the waitAquire rather
than the bottom,
and the process truly cannot proceed past that point until it gains
the lock. I have this working if StackInterpreterPrimitives holds the
primitive, but if I move the primitive to InterpreterPrimitives,
instructionPointer is unknown.

 
In general, you implement in InterpreterPrimitives the primitives that would work with the Interpreter, and in StackInterpreterPrimitives the ones specific to the StackInterpreter. If you have a bug in InterpreterPrimitives, it's likely to be specific to the StackInterpreter.

In the future the Cog branch may merge with the trunk, hence Interpreter will be back in the hierarchy. 
 

P.S. For the curious, here is the proof of concept I tried.  A single
call to the primitive counts up to four by backing up the
instructionPointer such that the primitive is executed again, until
the exit condition of four is reached.

(Note the use of Semaphore and ExcessSignalsIndex is not significant,
just an expedient template I was familiar with.)

# VM SIDE...

StackInterpreterPrimitives >> primitiveRetryExperiment
    | excessSignals stackTop |
    stackTop := self stackTop.
    excessSignals := objectMemory fetchInteger: ExcessSignalsIndex
ofObject: stackTop.
    excessSignals := excessSignals + 1.
    objectMemory storeInteger: ExcessSignalsIndex
        ofObject: stackTop
        withValue: excessSignals.
    [ excessSignals > 3 ] ifFalse: [ instructionPointer :=
instructionPointer - 1 ].

StackInterpreter class >> initializePrimitiveTable
    (234 primitiveRetryExperiment)


... Why instructionPointer - 1 ? It works if the send is encoded in a single byte as by chance is the case in your example, else your interpretation get misaligned, which is a complete nonsense (unless you're working with a Smalltalk-78 VM ;-) ). Going backward in the instructions is not that trivial, you need a scanner to find the previous pc. See #skipBackBeforeJump for example, which goes backward 1 instruction in the image side. You need to implement something similar in the interpreter if you want to do that... but you don't. 

Although going back one instruction is very funny, it won't work with the JIT, unless you do something completely evil, crazy and hackish. Most likely you want in fact to implement your primitive with a while loop instead, so you don't need that ip modification hack. Why didn't you do a while loop in the first place ? Primitive calls are not interrupt points anyway, it would be exactly the same behavior, wouldn't it ?
 

# IMAGE SIDE...

Semaphore subclass: #PrimExp
    instanceVariableNames: ''
    classVariableNames: ''
    package: '0PrimitiveRetryExperiment'

PrimExp >> initialize
    excessSignals := 1.

PrimExp >> primRetryExperiment
    <primitive: 234>

PrimExp >> excessSignals
    ^ excessSignals

# TEST CASE...

PrimExp new primRetryExperiment excessSignals
    --> 4

I've only done this with the Stack VM so far.  I'll report further
when I try it with Cog.


It's nice to see people trying to hack the VM :-). I'll try to answer your other questions.
 
cheers -ben

Reply | Threaded
Open this post in threaded view
|

Re: Interpreter versus StackInterpreter hierarchy

Ben Coman

On Fri, May 20, 2016 at 9:25 PM, Clément Bera <[hidden email]> wrote:

>
>
>
> On Thu, May 19, 2016 at 3:42 PM, Ben Coman <[hidden email]> wrote:
>>
>>
>> The hierarchy goes
>>   VMClass
>>      InterpreterPrimitives
>>         StackIntepreter
>>           StackIntepreterPrimitives
>>              CoInterpreter
>>                CoInterpreterPrimitives
>>
>> from which a tick / tock (XXInterpreter / XXInterpreterPrimitives)
>> pattern is apparent,
>> and I wonder why Interpreter is missing above InterpreterPrimitives
>> sitting off to the side.  I guess it is something to do with
>> InterpreterPrimitives composing objectMemory as an instance variable
>> rather than inheriting from ObjectMemory as Interpeter does?
>
>
> I think this is exactly that.
>
>>
>> The reason I ask is that I'm trying a new approach to the OwnedLock primitives
>> where if waitAcquire primitive sleeps, when the process wakes up it
>> retries the primitive.
>> So effectively the process sleeps at the top of the waitAquire rather
>> than the bottom,
>> and the process truly cannot proceed past that point until it gains
>> the lock. I have this working if StackInterpreterPrimitives holds the
>> primitive, but if I move the primitive to InterpreterPrimitives,
>> instructionPointer is unknown.
>>
>
> In general, you implement in InterpreterPrimitives the primitives that would work with the Interpreter, and in StackInterpreterPrimitives the ones specific to the StackInterpreter. If you have a bug in InterpreterPrimitives, it's likely to be specific to the StackInterpreter.
>
> In the future the Cog branch may merge with the trunk, hence Interpreter will be back in the hierarchy.
>
>>
>>
>> P.S. For the curious, here is the proof of concept I tried.  A single
>> call to the primitive counts up to four by backing up the
>> instructionPointer such that the primitive is executed again, until
>> the exit condition of four is reached.
>>
>> (Note the use of Semaphore and ExcessSignalsIndex is not significant,
>> just an expedient template I was familiar with.)
>>
>> # VM SIDE...
>>
>> StackInterpreterPrimitives >> primitiveRetryExperiment
>>     | excessSignals stackTop |
>>     stackTop := self stackTop.
>>     excessSignals := objectMemory fetchInteger: ExcessSignalsIndex
>> ofObject: stackTop.
>>     excessSignals := excessSignals + 1.
>>     objectMemory storeInteger: ExcessSignalsIndex
>>         ofObject: stackTop
>>         withValue: excessSignals.
>>     [ excessSignals > 3 ] ifFalse: [ instructionPointer :=
>> instructionPointer - 1 ].
>>
>> StackInterpreter class >> initializePrimitiveTable
>>     (234 primitiveRetryExperiment)
>>
>
> ... Why instructionPointer - 1 ?

A random experiment before moving on to -2, -3 and -4.   Obviously I
don't know enough yet to have properly judged its impact.  Just poking
it with a stick to see what pops out, and following that old adage
that if you need something to be true, "assume it" until you learn
otherwise.  And whadayaknow..., it worked for the StackInterpreter.
And I've since learnt its not so easy for the JIT.

> It works if the send is encoded in a single byte as by chance is the case in your example, else your interpretation get misaligned, which is a complete nonsense (unless you're working with a Smalltalk-78 VM ;-) ). Going backward in the instructions is not that trivial, you need a scanner to find the previous pc.

I thought *maybe* that since the layout of the receiver is "known" (to
be an OwnedLock) the previous pc could be assumed at a known distance
up the stack - but maybe that is bad practice and trouble if the
layout changes for anyone subclassing OwnedLock.

> See #skipBackBeforeJump for example, which goes backward 1 instruction in the image side. You need to implement something similar in the interpreter if you want to do that... but you don't.

I'll take a look just for interest, but point taken.

> Although going back one instruction is very funny, it won't work with the JIT, unless you do something completely evil, crazy and hackish.

That was the advice I was looking for.  I don't want to be hackish ;)
 At least not in the final result.

> Most likely you want in fact to implement your primitive with a while loop instead, so you don't need that ip modification hack. Why didn't you do a while loop in the first place ?

A loop in the Image would work, but I'm attempting to keep it in the
VM.  IIUC a loop won't work in the VM because the primitive sleeps and
changes context if the lock is held by someone else.

> Primitive calls are not interrupt points anyway, it would be exactly the same behavior, wouldn't it ?
>
>>
>>
>> # IMAGE SIDE...
>>
>> Semaphore subclass: #PrimExp
>>     instanceVariableNames: ''
>>     classVariableNames: ''
>>     package: '0PrimitiveRetryExperiment'
>>
>> PrimExp >> initialize
>>     excessSignals := 1.
>>
>> PrimExp >> primRetryExperiment
>>     <primitive: 234>
>>
>> PrimExp >> excessSignals
>>     ^ excessSignals
>>
>> # TEST CASE...
>>
>> PrimExp new primRetryExperiment excessSignals
>>     --> 4
>>
>> I've only done this with the Stack VM so far.  I'll report further
>> when I try it with Cog.

So I found the approach doesn't work with Cog.
cheers -ben

>
> It's nice to see people trying to hack the VM :-). I'll try to answer your other questions.
Reply | Threaded
Open this post in threaded view
|

Re: Interpreter versus StackInterpreter hierarchy

Clément Béra
 


On Fri, May 20, 2016 at 7:51 PM, Ben Coman <[hidden email]> wrote:

On Fri, May 20, 2016 at 9:25 PM, Clément Bera <[hidden email]> wrote:
>
>
>
> On Thu, May 19, 2016 at 3:42 PM, Ben Coman <[hidden email]> wrote:
>>
>>
>> The hierarchy goes
>>   VMClass
>>      InterpreterPrimitives
>>         StackIntepreter
>>           StackIntepreterPrimitives
>>              CoInterpreter
>>                CoInterpreterPrimitives
>>
>> from which a tick / tock (XXInterpreter / XXInterpreterPrimitives)
>> pattern is apparent,
>> and I wonder why Interpreter is missing above InterpreterPrimitives
>> sitting off to the side.  I guess it is something to do with
>> InterpreterPrimitives composing objectMemory as an instance variable
>> rather than inheriting from ObjectMemory as Interpeter does?
>
>
> I think this is exactly that.
>
>>
>> The reason I ask is that I'm trying a new approach to the OwnedLock primitives
>> where if waitAcquire primitive sleeps, when the process wakes up it
>> retries the primitive.
>> So effectively the process sleeps at the top of the waitAquire rather
>> than the bottom,
>> and the process truly cannot proceed past that point until it gains
>> the lock. I have this working if StackInterpreterPrimitives holds the
>> primitive, but if I move the primitive to InterpreterPrimitives,
>> instructionPointer is unknown.
>>
>
> In general, you implement in InterpreterPrimitives the primitives that would work with the Interpreter, and in StackInterpreterPrimitives the ones specific to the StackInterpreter. If you have a bug in InterpreterPrimitives, it's likely to be specific to the StackInterpreter.
>
> In the future the Cog branch may merge with the trunk, hence Interpreter will be back in the hierarchy.
>
>>
>>
>> P.S. For the curious, here is the proof of concept I tried.  A single
>> call to the primitive counts up to four by backing up the
>> instructionPointer such that the primitive is executed again, until
>> the exit condition of four is reached.
>>
>> (Note the use of Semaphore and ExcessSignalsIndex is not significant,
>> just an expedient template I was familiar with.)
>>
>> # VM SIDE...
>>
>> StackInterpreterPrimitives >> primitiveRetryExperiment
>>     | excessSignals stackTop |
>>     stackTop := self stackTop.
>>     excessSignals := objectMemory fetchInteger: ExcessSignalsIndex
>> ofObject: stackTop.
>>     excessSignals := excessSignals + 1.
>>     objectMemory storeInteger: ExcessSignalsIndex
>>         ofObject: stackTop
>>         withValue: excessSignals.
>>     [ excessSignals > 3 ] ifFalse: [ instructionPointer :=
>> instructionPointer - 1 ].
>>
>> StackInterpreter class >> initializePrimitiveTable
>>     (234 primitiveRetryExperiment)
>>
>
> ... Why instructionPointer - 1 ?

A random experiment before moving on to -2, -3 and -4.   Obviously I
don't know enough yet to have properly judged its impact.  Just poking
it with a stick to see what pops out, and following that old adage
that if you need something to be true, "assume it" until you learn
otherwise.  And whadayaknow..., it worked for the StackInterpreter.
And I've since learnt its not so easy for the JIT.

> It works if the send is encoded in a single byte as by chance is the case in your example, else your interpretation get misaligned, which is a complete nonsense (unless you're working with a Smalltalk-78 VM ;-) ). Going backward in the instructions is not that trivial, you need a scanner to find the previous pc.

I thought *maybe* that since the layout of the receiver is "known" (to
be an OwnedLock) the previous pc could be assumed at a known distance
up the stack - but maybe that is bad practice and trouble if the
layout changes for anyone subclassing OwnedLock.


I don' really understand that known layout of the receiver thing. 

The problem is with the encoding of sends in the bytecode. They are encoded in different number of bytes to lower the memory footprint.

For example, in Pharo, in this method:
foo
    PrimExp new primRetryExperiment excessSignals

=> 27 <D1> send: primRetryExperiment

the send to primRetryExperiment is encoded in a single byte.

But in this method:
foo
  self foo1 foo2 foo3 foo4 foo5 foo6 foo7 foo8 
    self foo9 foo10 foo11 foo12 foo13 foo14 foo15 foo16.
    PrimExp new primRetryExperiment excessSignals

=> 109 <83 11> send: primRetryExperiment

The same send is encoded in 2 bytes.

So, after the send, in the primitive code, you need the instruction pointer to go back by 1 or 2 bytes to repeat the send. But you don't know by how many bytes. There is no easy way to guess if it's 1 or 2 (or something else, there are other cases I omitted).
 
> See #skipBackBeforeJump for example, which goes backward 1 instruction in the image side. You need to implement something similar in the interpreter if you want to do that... but you don't.

I'll take a look just for interest, but point taken.

> Although going back one instruction is very funny, it won't work with the JIT, unless you do something completely evil, crazy and hackish.

That was the advice I was looking for.  I don't want to be hackish ;)
 At least not in the final result.

> Most likely you want in fact to implement your primitive with a while loop instead, so you don't need that ip modification hack. Why didn't you do a while loop in the first place ?

A loop in the Image would work, but I'm attempting to keep it in the
VM.  IIUC a loop won't work in the VM because the primitive sleeps and
changes context if the lock is held by someone else.

hum. If I change your example to:

StackInterpreterPrimitives >> primitiveRetryExperiment
     | excessSignals stackTop |
     stackTop := self stackTop.
     excessSignals := objectMemory fetchInteger: ExcessSignalsIndex ofObject: stackTop.
     [ excessSignals > 3 ] whileFalse: [
         excessSignals := excessSignals + 1.
         objectMemory storeInteger: ExcessSignalsIndex
             ofObject: stackTop
             withValue: excessSignals ]. 

It's exactly equivalent to what you wrote, isn't it ? There is no process switch - context switch - in both cases in the loop, isn't it ? Or maybe I am missing something ?


> Primitive calls are not interrupt points anyway, it would be exactly the same behavior, wouldn't it ?
>
>>
>>
>> # IMAGE SIDE...
>>
>> Semaphore subclass: #PrimExp
>>     instanceVariableNames: ''
>>     classVariableNames: ''
>>     package: '0PrimitiveRetryExperiment'
>>
>> PrimExp >> initialize
>>     excessSignals := 1.
>>
>> PrimExp >> primRetryExperiment
>>     <primitive: 234>
>>
>> PrimExp >> excessSignals
>>     ^ excessSignals
>>
>> # TEST CASE...
>>
>> PrimExp new primRetryExperiment excessSignals
>>     --> 4
>>
>> I've only done this with the Stack VM so far.  I'll report further
>> when I try it with Cog.

So I found the approach doesn't work with Cog.
cheers -ben

>
> It's nice to see people trying to hack the VM :-). I'll try to answer your other questions.

Reply | Threaded
Open this post in threaded view
|

Re: Interpreter versus StackInterpreter hierarchy

Ben Coman

On Sat, May 21, 2016 at 4:36 AM, Clément Bera <[hidden email]> wrote:
> On Fri, May 20, 2016 at 7:51 PM, Ben Coman <[hidden email]> wrote:
>> On Fri, May 20, 2016 at 9:25 PM, Clément Bera <[hidden email]> wrote:
>> > On Thu, May 19, 2016 at 3:42 PM, Ben Coman <[hidden email]> wrote:

>> >> P.S. For the curious, here is the proof of concept I tried.  A single
>> >> call to the primitive counts up to four by backing up the
>> >> instructionPointer such that the primitive is executed again, until
>> >> the exit condition of four is reached.
>> >>
>> >> (Note the use of Semaphore and ExcessSignalsIndex is not significant,
>> >> just an expedient template I was familiar with.)
>> >>
>> >> # VM SIDE...
>> >>
>> >> StackInterpreterPrimitives >> primitiveRetryExperiment
>> >>     | excessSignals stackTop |
>> >>     stackTop := self stackTop.
>> >>     excessSignals := objectMemory fetchInteger: ExcessSignalsIndex
>> >> ofObject: stackTop.
>> >>     excessSignals := excessSignals + 1.
>> >>     objectMemory storeInteger: ExcessSignalsIndex
>> >>         ofObject: stackTop
>> >>         withValue: excessSignals.
>> >>     [ excessSignals > 3 ] ifFalse: [ instructionPointer :=
>> >> instructionPointer - 1 ].
>> >>
>> >> StackInterpreter class >> initializePrimitiveTable
>> >>     (234 primitiveRetryExperiment)
>> >>
>> >
>> > ... Why instructionPointer - 1 ?
>>
>> A random experiment before moving on to -2, -3 and -4.   Obviously I
>> don't know enough yet to have properly judged its impact.  Just poking
>> it with a stick to see what pops out, and following that old adage
>> that if you need something to be true, "assume it" until you learn
>> otherwise.  And whadayaknow..., it worked for the StackInterpreter.
>> And I've since learnt its not so easy for the JIT.
>>
>> > It works if the send is encoded in a single byte as by chance is the case in your example, else your interpretation get misaligned, which is a complete nonsense (unless you're working with a Smalltalk-78 VM ;-) ). Going backward in the instructions is not that trivial, you need a scanner to find the previous pc.
>>
>> I thought *maybe* that since the layout of the receiver is "known" (to
>> be an OwnedLock) the previous pc could be assumed at a known distance
>> up the stack - but maybe that is bad practice and trouble if the
>> layout changes for anyone subclassing OwnedLock.
>
> I don' really understand that known layout of the receiver thing.

Just my limited understanding anf naive assumption.  The course I took
on compilers was 20 years ago. You counter example below helps...


> The problem is with the encoding of sends in the bytecode. They are encoded in different number of bytes to lower the memory footprint.
>
> For example, in Pharo, in this method:
> foo
>     PrimExp new primRetryExperiment excessSignals
>
> => 27 <D1> send: primRetryExperiment
>
> the send to primRetryExperiment is encoded in a single byte.
>
> But in this method:
> foo
>   self foo1 foo2 foo3 foo4 foo5 foo6 foo7 foo8
>     self foo9 foo10 foo11 foo12 foo13 foo14 foo15 foo16.
>     PrimExp new primRetryExperiment excessSignals
>
> => 109 <83 11> send: primRetryExperiment
>
> The same send is encoded in 2 bytes.

> So, after the send, in the primitive code, you need the instruction pointer to go back by 1 or 2 bytes to repeat the send. But you don't know by how many bytes. There is no easy way to guess if it's 1 or 2 (or something else, there are other cases I omitted).


Okay. That helps me understand of my task better.

>> > See #skipBackBeforeJump for example, which goes backward 1 instruction in the image side. You need to implement something similar in the interpreter if you want to do that... but you don't.
>>
>> I'll take a look just for interest, but point taken.
>>
>> > Although going back one instruction is very funny, it won't work with the JIT, unless you do something completely evil, crazy and hackish.
>>
>> That was the advice I was looking for.  I don't want to be hackish ;)
>>  At least not in the final result.
>>
>> > Most likely you want in fact to implement your primitive with a while loop instead, so you don't need that ip modification hack. Why didn't you do a while loop in the first place ?
>>
>> A loop in the Image would work, but I'm attempting to keep it in the
>> VM.  IIUC a loop won't work in the VM because the primitive sleeps and
>> changes context if the lock is held by someone else.
>
>
> hum. If I change your example to:
>
> StackInterpreterPrimitives >> primitiveRetryExperiment
>      | excessSignals stackTop |
>      stackTop := self stackTop.
>      excessSignals := objectMemory fetchInteger: ExcessSignalsIndex ofObject: stackTop.
>      [ excessSignals > 3 ] whileFalse: [
>          excessSignals := excessSignals + 1.
>          objectMemory storeInteger: ExcessSignalsIndex
>              ofObject: stackTop
>              withValue: excessSignals ].
>
> It's exactly equivalent to what you wrote, isn't it ? There is no process switch - context switch - in both cases in the loop, isn't it ? Or maybe I am missing something ?

Apologies for mis-leading the discussion. The missing bit is, the
above isn't my actually requirement.  Its only an experiment of the
effect of modifying the instruction pointer. My real use case is for
the OwnedLock primitives I'm introducing [1], which at the end of
primitiveOwnedLockWaitAcquire.

    self transferTo: self wakeHighestPriority from: CSOwnedLockWaitAcquire.
    self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter.

That code works well, except for one corner case identified by Dennis
where after primitiveOwnedLockRelease hands the lock to a waiting
process, that process could be terminated before waking up.  Doing
that in primitiveOwnedLockRelease is required because when
primitiveOwnedLockWaitAcquire goes to sleep, you've already past its
code that acquires the lock.

Mutex>>critical: mutuallyExcludedBlock
    ^[  lock waitAcquire
             ifNil: mutuallyExcludedBlock
             ifNotNil: mutuallyExcludedBlock
      ] ensure: [lock release].

instead of the faster...
Mutex>>critical: mutuallyExcludedBlock
    ^lock waitAcquire
        ifNil: mutuallyExcludedBlock
        ifNotNil:[ mutuallyExcludedBlock ensure: [lock release] ].

I'd heard about Eliot "retrying primitives" for forwarding failures
and considered a solution might be for primitiveOwnedLockWaitAcquire
to be re-executed when its process woke up.  So the lock is only
acquired after the process wakes up, rather than being handed to it
while it was asleep.  Conceptually the process sleeps at the top of
the primitive rather than the bottom.

I found what Eliot does...
     dispatchFunctionPointer(primitiveFunctionPointer);
      /* begin maybeRetryFailureDueToForwarding */
      if (GIV(primFailCode)
       && (checkForAndFollowForwardedPrimitiveState())) {
              /* begin initPrimCall */
              GIV(primFailCode) = 0;
              dispatchFunctionPointer(primitiveFunctionPointer);
      }

but I guess that won't work when switching processes.  So having
caught the idea for primitive retry, I went looking for another way
that worked across a process switch, and learn a bit more about the VM
in the process.   Hence my experiment to naively decrement the
instruction pointer before switching context.

[1] http://forum.world.st/OwnedLock-primitives-request-for-review-td4886130.html

cheers -ben

>>
>> > Primitive calls are not interrupt points anyway, it would be exactly the same behavior, wouldn't it ?
>> >
>> >>
>> >>
>> >> # IMAGE SIDE...
>> >>
>> >> Semaphore subclass: #PrimExp
>> >>     instanceVariableNames: ''
>> >>     classVariableNames: ''
>> >>     package: '0PrimitiveRetryExperiment'
>> >>
>> >> PrimExp >> initialize
>> >>     excessSignals := 1.
>> >>
>> >> PrimExp >> primRetryExperiment
>> >>     <primitive: 234>
>> >>
>> >> PrimExp >> excessSignals
>> >>     ^ excessSignals
>> >>
>> >> # TEST CASE...
>> >>
>> >> PrimExp new primRetryExperiment excessSignals
>> >>     --> 4
>> >>
>> >> I've only done this with the Stack VM so far.  I'll report further
>> >> when I try it with Cog.
>>
>> So I found the approach doesn't work with Cog.
>> cheers -ben
>>
>> >
>> > It's nice to see people trying to hack the VM :-). I'll try to answer your other questions.
Reply | Threaded
Open this post in threaded view
|

Re: Interpreter versus StackInterpreter hierarchy

Eliot Miranda-2
 
Hi Ben, Hi Denis, Hi Clément,

On Fri, May 20, 2016 at 7:52 PM, Ben Coman <[hidden email]> wrote:

On Sat, May 21, 2016 at 4:36 AM, Clément Bera <[hidden email]> wrote:
> On Fri, May 20, 2016 at 7:51 PM, Ben Coman <[hidden email]> wrote:
>> On Fri, May 20, 2016 at 9:25 PM, Clément Bera <[hidden email]> wrote:
>> > On Thu, May 19, 2016 at 3:42 PM, Ben Coman <[hidden email]> wrote:

>> >> P.S. For the curious, here is the proof of concept I tried.  A single
>> >> call to the primitive counts up to four by backing up the
>> >> instructionPointer such that the primitive is executed again, until
>> >> the exit condition of four is reached.
>> >>
>> >> (Note the use of Semaphore and ExcessSignalsIndex is not significant,
>> >> just an expedient template I was familiar with.)
>> >>
>> >> # VM SIDE...
>> >>
>> >> StackInterpreterPrimitives >> primitiveRetryExperiment
>> >>     | excessSignals stackTop |
>> >>     stackTop := self stackTop.
>> >>     excessSignals := objectMemory fetchInteger: ExcessSignalsIndex
>> >> ofObject: stackTop.
>> >>     excessSignals := excessSignals + 1.
>> >>     objectMemory storeInteger: ExcessSignalsIndex
>> >>         ofObject: stackTop
>> >>         withValue: excessSignals.
>> >>     [ excessSignals > 3 ] ifFalse: [ instructionPointer :=
>> >> instructionPointer - 1 ].
>> >>
>> >> StackInterpreter class >> initializePrimitiveTable
>> >>     (234 primitiveRetryExperiment)
>> >>
>> >
>> > ... Why instructionPointer - 1 ?
>>
>> A random experiment before moving on to -2, -3 and -4.   Obviously I
>> don't know enough yet to have properly judged its impact.  Just poking
>> it with a stick to see what pops out, and following that old adage
>> that if you need something to be true, "assume it" until you learn
>> otherwise.  And whadayaknow..., it worked for the StackInterpreter.
>> And I've since learnt its not so easy for the JIT.
>>
>> > It works if the send is encoded in a single byte as by chance is the case in your example, else your interpretation get misaligned, which is a complete nonsense (unless you're working with a Smalltalk-78 VM ;-) ). Going backward in the instructions is not that trivial, you need a scanner to find the previous pc.
>>
>> I thought *maybe* that since the layout of the receiver is "known" (to
>> be an OwnedLock) the previous pc could be assumed at a known distance
>> up the stack - but maybe that is bad practice and trouble if the
>> layout changes for anyone subclassing OwnedLock.
>
> I don' really understand that known layout of the receiver thing.

Just my limited understanding anf naive assumption.  The course I took
on compilers was 20 years ago. You counter example below helps...


> The problem is with the encoding of sends in the bytecode. They are encoded in different number of bytes to lower the memory footprint.
>
> For example, in Pharo, in this method:
> foo
>     PrimExp new primRetryExperiment excessSignals
>
> => 27 <D1> send: primRetryExperiment
>
> the send to primRetryExperiment is encoded in a single byte.
>
> But in this method:
> foo
>   self foo1 foo2 foo3 foo4 foo5 foo6 foo7 foo8
>     self foo9 foo10 foo11 foo12 foo13 foo14 foo15 foo16.
>     PrimExp new primRetryExperiment excessSignals
>
> => 109 <83 11> send: primRetryExperiment
>
> The same send is encoded in 2 bytes.

> So, after the send, in the primitive code, you need the instruction pointer to go back by 1 or 2 bytes to repeat the send. But you don't know by how many bytes. There is no easy way to guess if it's 1 or 2 (or something else, there are other cases I omitted).


Okay. That helps me understand of my task better.

>> > See #skipBackBeforeJump for example, which goes backward 1 instruction in the image side. You need to implement something similar in the interpreter if you want to do that... but you don't.
>>
>> I'll take a look just for interest, but point taken.
>>
>> > Although going back one instruction is very funny, it won't work with the JIT, unless you do something completely evil, crazy and hackish.
>>
>> That was the advice I was looking for.  I don't want to be hackish ;)
>>  At least not in the final result.
>>
>> > Most likely you want in fact to implement your primitive with a while loop instead, so you don't need that ip modification hack. Why didn't you do a while loop in the first place ?
>>
>> A loop in the Image would work, but I'm attempting to keep it in the
>> VM.  IIUC a loop won't work in the VM because the primitive sleeps and
>> changes context if the lock is held by someone else.
>
>
> hum. If I change your example to:
>
> StackInterpreterPrimitives >> primitiveRetryExperiment
>      | excessSignals stackTop |
>      stackTop := self stackTop.
>      excessSignals := objectMemory fetchInteger: ExcessSignalsIndex ofObject: stackTop.
>      [ excessSignals > 3 ] whileFalse: [
>          excessSignals := excessSignals + 1.
>          objectMemory storeInteger: ExcessSignalsIndex
>              ofObject: stackTop
>              withValue: excessSignals ].
>
> It's exactly equivalent to what you wrote, isn't it ? There is no process switch - context switch - in both cases in the loop, isn't it ? Or maybe I am missing something ?

Apologies for mis-leading the discussion. The missing bit is, the
above isn't my actually requirement.  Its only an experiment of the
effect of modifying the instruction pointer. My real use case is for
the OwnedLock primitives I'm introducing [1], which at the end of
primitiveOwnedLockWaitAcquire.

    self transferTo: self wakeHighestPriority from: CSOwnedLockWaitAcquire.
    self forProcessPrimitiveReturnToExecutivePostContextSwitch: inInterpreter.

That code works well, except for one corner case identified by Dennis
where after primitiveOwnedLockRelease hands the lock to a waiting
process, that process could be terminated before waking up. 

There is a better way of solving this, and that is to use a pragma to identify a method that contains such a suspension point, and have the process terminate code look for the pragma and act accordingly.  For example, the pragma could have a terminate action, sent to the receiver with the context as argument, e.g.

Mutex>>critical: mutuallyExcludedBlock
    <onTerminate: #ensureMutexUnlockedInCritical:>
    ^lock waitAcquire
        ifNil: mutuallyExcludedBlock
        ifNotNil:[ mutuallyExcludedBlock ensure: [lock release] ]

(and here I'm guessing...)

Mutex>> ensureMutexUnlockedInCritical: aContext
    "long-winded comment explaining the corner case, referencing tests, etc, etc and how it is solved on terminate buy this method"
    (aContext pc = aContext initialPC
     and: [self inTheCorner]) ifTrue:
        [self doTheRightThingTM]

So on terminate the stack is walked (it is anyway) looking for unwinds or onTerminate: markers.  Any onTerminate: markers are evaluated, and the corner case is solved.  The pragma approach also allows for visibility in the code.


Doing
that in primitiveOwnedLockRelease is required because when
primitiveOwnedLockWaitAcquire goes to sleep, you've already past its
code that acquires the lock.

Mutex>>critical: mutuallyExcludedBlock
    ^[  lock waitAcquire
             ifNil: mutuallyExcludedBlock
             ifNotNil: mutuallyExcludedBlock
      ] ensure: [lock release].

instead of the faster...
Mutex>>critical: mutuallyExcludedBlock
    ^lock waitAcquire
        ifNil: mutuallyExcludedBlock
        ifNotNil:[ mutuallyExcludedBlock ensure: [lock release] ].

I'd heard about Eliot "retrying primitives" for forwarding failures
and considered a solution might be for primitiveOwnedLockWaitAcquire
to be re-executed when its process woke up.  So the lock is only
acquired after the process wakes up, rather than being handed to it
while it was asleep.  Conceptually the process sleeps at the top of
the primitive rather than the bottom.

I found what Eliot does...
     dispatchFunctionPointer(primitiveFunctionPointer);
      /* begin maybeRetryFailureDueToForwarding */
      if (GIV(primFailCode)
       && (checkForAndFollowForwardedPrimitiveState())) {
              /* begin initPrimCall */
              GIV(primFailCode) = 0;
              dispatchFunctionPointer(primitiveFunctionPointer);
      }

but I guess that won't work when switching processes.  So having
caught the idea for primitive retry, I went looking for another way
that worked across a process switch, and learn a bit more about the VM
in the process.   Hence my experiment to naively decrement the
instruction pointer before switching context.

[1] http://forum.world.st/OwnedLock-primitives-request-for-review-td4886130.html

cheers -ben

>>
>> > Primitive calls are not interrupt points anyway, it would be exactly the same behavior, wouldn't it ?
>> >
>> >>
>> >>
>> >> # IMAGE SIDE...
>> >>
>> >> Semaphore subclass: #PrimExp
>> >>     instanceVariableNames: ''
>> >>     classVariableNames: ''
>> >>     package: '0PrimitiveRetryExperiment'
>> >>
>> >> PrimExp >> initialize
>> >>     excessSignals := 1.
>> >>
>> >> PrimExp >> primRetryExperiment
>> >>     <primitive: 234>
>> >>
>> >> PrimExp >> excessSignals
>> >>     ^ excessSignals
>> >>
>> >> # TEST CASE...
>> >>
>> >> PrimExp new primRetryExperiment excessSignals
>> >>     --> 4
>> >>
>> >> I've only done this with the Stack VM so far.  I'll report further
>> >> when I try it with Cog.
>>
>> So I found the approach doesn't work with Cog.
>> cheers -ben
>>
>> >
>> > It's nice to see people trying to hack the VM :-). I'll try to answer your other questions.



--
_,,,^..^,,,_
best, Eliot