I'm confused about Process>>isTerminated

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

I'm confused about Process>>isTerminated

Max Leske
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
    and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.


isDead
        ^ pc isNil


Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)
- a properly terminated process will raise an MNU (although apparently not always…?)
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?


Cheers,
Max
Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Eliot Miranda-2
Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 
isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?
 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.
 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.
 

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?


Cheers,
Max



--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Max Leske
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
 "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
"This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

Cheers,
Max

 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.
 

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?


Cheers,
Max



--
best,
Eliot

Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Eliot Miranda-2
Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
 "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
"This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


Cheers,
Max

 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.
 

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?


Cheers,
Max

--
best,
Eliot

--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Max Leske
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

Cheers,
Max



Cheers,
Max

 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.
 

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?


Cheers,
Max

-- 
best,
Eliot

-- 
best,
Eliot

Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Eliot Miranda-2
Hi Max,

    phhh, time zone differences suck ;-)

On Thu, Sep 18, 2014 at 3:50 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

I can't see anything to do other than waiting.   One thing is to run the process at as close to user priority as possible, so I would say

proc := [ Semaphore new wait ] forkAt: Processor activePriority - 1.
 
Another important thing is that you're not giving your process a chance to run before you test for it not terminating.  So adding a yield after the first set of asserts and then repeating them is good:

started := false.
proc := [ started := true. Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait.
self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.

Another thing might be to boost its priority to make sure it finishes (except that that'll probably have no effect because IIRC right now the terminator runs the termination).  So you could say

proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.

process priority: Processor activePriority + 1.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].

Further I'd want to test that unwind blocks have been run so I'd say

testIsTerminated
| proc started unwound terminator |
unwound := false.
proc := [   started := true.
[Semaphore new wait]
ensure: [terminator := Processor activeProcess.
unwound := true] ]
forkAt: Processor activePriority - 1.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. "Alloc proc to run; there shouldnt be too much else going on so this delay should suffice"

self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
proc priority: Processor activePriority + 1. "This may have no effect; termination may be executed by the terminator rather than the terminatee; ys, this is a bug"
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
(Delay forMilliseconds: 10) wait. "Allow proc to terminate;  there shouldnt be too much else going on so this delay should suffice"

self assert: proc isTerminated.
self assert: proc isTerminating.
self assert: unwound.
self assert: terminator == proc. "But this should be made an expected failure; I don't know how to do that in SUnit..."

and google's mail text editor *SUCKS*!!!!

Cheers,
Max
Cheers,
Max 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?

Cheers,
Max
-- 
best,
Eliot
-- 
best,
Eliot
--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Bob Westergaard
Why not use #waitTimeoutMsecs:?   Something like:

  greenLight := Semaphore new.
  process :=
    [started := true.
    [Semaphore new wait] ensure:
        [terminator := Processor activeProcess.
        unwound := true].
     greenLight signal] forkAt: Processor activeProcess priority -1.

  expired := greenLight waitTimeoutMSecs: 1000. "or whatever suits you"
  deny: expired.
  assert: process isTerminated.
  " and so on"

-- Bob

Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Max Leske
Thanks for the pointer.

On 18.09.2014, at 22:52, Bob Westergaard <[hidden email]> wrote:

> Why not use #waitTimeoutMsecs:?   Something like:
>
>  greenLight := Semaphore new.
>  process :=
>    [started := true.
>    [Semaphore new wait] ensure:

I think that should be “[greenLight wait]”, shouldn’t it?

>        [terminator := Processor activeProcess.
>        unwound := true].
>     greenLight signal] forkAt: Processor activeProcess priority -1.
>
>  expired := greenLight waitTimeoutMSecs: 1000. "or whatever suits you"
>  deny: expired.
>  assert: process isTerminated.
>  " and so on"
>
> -- Bob
>


Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Max Leske

On 22.09.2014, at 09:47, Max Leske <[hidden email]> wrote:

> Thanks for the pointer.
>
> On 18.09.2014, at 22:52, Bob Westergaard <[hidden email]> wrote:
>
>> Why not use #waitTimeoutMsecs:?   Something like:
>>
>> greenLight := Semaphore new.
>> process :=
>>   [started := true.
>>   [Semaphore new wait] ensure:
>
> I think that should be “[greenLight wait]”, shouldn’t it?

Sorry, you’re right. I should have thoroughly read Eliot’s e-mail first :)

>
>>       [terminator := Processor activeProcess.
>>       unwound := true].
>>    greenLight signal] forkAt: Processor activeProcess priority -1.
>>
>> expired := greenLight waitTimeoutMSecs: 1000. "or whatever suits you"
>> deny: expired.
>> assert: process isTerminated.
>> " and so on"
>>
>> -- Bob
>>
>


Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Max Leske
In reply to this post by Eliot Miranda-2
Hi Eliot,

Thanks a lot for those explanations.

On 18.09.2014, at 20:53, Eliot Miranda <[hidden email]> wrote:

Hi Max,

    phhh, time zone differences suck ;-)

On Thu, Sep 18, 2014 at 3:50 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

I can't see anything to do other than waiting.   One thing is to run the process at as close to user priority as possible, so I would say

proc := [ Semaphore new wait ] forkAt: Processor activePriority - 1.
 
Another important thing is that you're not giving your process a chance to run before you test for it not terminating.  So adding a yield after the first set of asserts and then repeating them is good:

started := false. proc := [ started := true. Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.

Another thing might be to boost its priority to make sure it finishes (except that that'll probably have no effect because IIRC right now the terminator runs the termination).  So you could say

proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.

process priority: Processor activePriority + 1.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].

Further I'd want to test that unwind blocks have been run so I'd say

testIsTerminated
| proc started unwound terminator |
unwound := false. proc := [   started := true. [Semaphore new wait]
ensure: [terminator := Processor activeProcess.
unwound := true] ]
forkAt: Processor activePriority - 1.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. "Alloc proc to run; there shouldnt be too much else going on so this delay should suffice"

self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
proc priority: Processor activePriority + 1. "This may have no effect; termination may be executed by the terminator rather than the terminatee; ys, this is a bug"
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
(Delay forMilliseconds: 10) wait. "Allow proc to terminate;  there shouldnt be too much else going on so this delay should suffice"

self assert: proc isTerminated.
self assert: proc isTerminating.
self assert: unwound.
self assert: terminator == proc. "But this should be made an expected failure; I don't know how to do that in SUnit…"

From your comments I expected this last statement to fail but actually it doesn’t. I guess that’s a good sign (?).


and google's mail text editor *SUCKS*!!!!

lol :p

I noticed something else regarding terminated processes that have never run and I’m not sure if that’s not a bug:
When I suspend a process (that has never run) that is not the active process, I can reliably reproduce that the entire #terminate method is being executed. The process’ suspendedContext is the bottom context (as it should be). However, the pc is equal to the startpc, since that process never had a chance to to anything. The result is that #isTerminated will answer false, even though the process is technically terminated.
One side effect of this is that it’s impossible to do something like “[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].” because that will not terminate for all processes. Luckily those processes can be garbage collected regardless of what #isTerminated says.

One obvious fix would be to set the pc of the suspendedContext to nil but I’m not sure that’s a good idea.

What do you think?

Cheers,
Max


Cheers,
Max
Cheers,
Max 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?

Cheers,
Max
-- 
best,
Eliot
-- 
best,
Eliot
-- 
best,
Eliot

Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Eliot Miranda-2


On Mon, Sep 22, 2014 at 4:57 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

Thanks a lot for those explanations.

On 18.09.2014, at 20:53, Eliot Miranda <[hidden email]> wrote:

Hi Max,

    phhh, time zone differences suck ;-)

On Thu, Sep 18, 2014 at 3:50 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

I can't see anything to do other than waiting.   One thing is to run the process at as close to user priority as possible, so I would say

proc := [ Semaphore new wait ] forkAt: Processor activePriority - 1.
 
Another important thing is that you're not giving your process a chance to run before you test for it not terminating.  So adding a yield after the first set of asserts and then repeating them is good:

started := false. proc := [ started := true. Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.

Another thing might be to boost its priority to make sure it finishes (except that that'll probably have no effect because IIRC right now the terminator runs the termination).  So you could say

proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.

process priority: Processor activePriority + 1.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].

Further I'd want to test that unwind blocks have been run so I'd say

testIsTerminated
| proc started unwound terminator |
unwound := false. proc := [   started := true. [Semaphore new wait]
ensure: [terminator := Processor activeProcess.
unwound := true] ]
forkAt: Processor activePriority - 1.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. "Alloc proc to run; there shouldnt be too much else going on so this delay should suffice"

self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
proc priority: Processor activePriority + 1. "This may have no effect; termination may be executed by the terminator rather than the terminatee; ys, this is a bug"
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
(Delay forMilliseconds: 10) wait. "Allow proc to terminate;  there shouldnt be too much else going on so this delay should suffice"

self assert: proc isTerminated.
self assert: proc isTerminating.
self assert: unwound.
self assert: terminator == proc. "But this should be made an expected failure; I don't know how to do that in SUnit…"

From your comments I expected this last statement to fail but actually it doesn’t. I guess that’s a good sign (?).

Yes, that's great!
 


and google's mail text editor *SUCKS*!!!!

lol :p

I spent so much time editing the code in the message with the editor doing weird things like pasting the fragment I was appending to a line to the end of the previous line, etc.  Drove me *mad* :-)


I noticed something else regarding terminated processes that have never run and I’m not sure if that’s not a bug:
When I suspend a process (that has never run) that is not the active process, I can reliably reproduce that the entire #terminate method is being executed. The process’ suspendedContext is the bottom context (as it should be). However, the pc is equal to the startpc, since that process never had a chance to to anything. The result is that #isTerminated will answer false, even though the process is technically terminated.

Hmmm.  You might want to add code to #terminated to check for that case, and set the pc to endPC + 1, or nil.  Just make sure there's a comment ;-)
 
One side effect of this is that it’s impossible to do something like “[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].” because that will not terminate for all processes. Luckily those processes can be garbage collected regardless of what #isTerminated says.

Right.

 

One obvious fix would be to set the pc of the suspendedContext to nil but I’m not sure that’s a good idea.

What do you think?
 

Cheers,
Max
Cheers,
Max
Cheers,
Max 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?

Cheers,
Max
-- 
best,
Eliot
-- 
best,
Eliot
-- 
best,
Eliot
--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Eliot Miranda-2
In reply to this post by Max Leske
Hi Max,

   phhh, that editor truncated my reply (that's my excuse and I'm sticking to it), so...

On Mon, Sep 22, 2014 at 4:57 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

Thanks a lot for those explanations.

On 18.09.2014, at 20:53, Eliot Miranda <[hidden email]> wrote:

Hi Max,

    phhh, time zone differences suck ;-)

On Thu, Sep 18, 2014 at 3:50 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

I can't see anything to do other than waiting.   One thing is to run the process at as close to user priority as possible, so I would say

proc := [ Semaphore new wait ] forkAt: Processor activePriority - 1.
 
Another important thing is that you're not giving your process a chance to run before you test for it not terminating.  So adding a yield after the first set of asserts and then repeating them is good:

started := false. proc := [ started := true. Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.

Another thing might be to boost its priority to make sure it finishes (except that that'll probably have no effect because IIRC right now the terminator runs the termination).  So you could say

proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.

process priority: Processor activePriority + 1.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].

Further I'd want to test that unwind blocks have been run so I'd say

testIsTerminated
| proc started unwound terminator |
unwound := false. proc := [   started := true. [Semaphore new wait]
ensure: [terminator := Processor activeProcess.
unwound := true] ]
forkAt: Processor activePriority - 1.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. "Alloc proc to run; there shouldnt be too much else going on so this delay should suffice"

self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
proc priority: Processor activePriority + 1. "This may have no effect; termination may be executed by the terminator rather than the terminatee; ys, this is a bug"
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
(Delay forMilliseconds: 10) wait. "Allow proc to terminate;  there shouldnt be too much else going on so this delay should suffice"

self assert: proc isTerminated.
self assert: proc isTerminating.
self assert: unwound.
self assert: terminator == proc. "But this should be made an expected failure; I don't know how to do that in SUnit…"

From your comments I expected this last statement to fail but actually it doesn’t. I guess that’s a good sign (?).


and google's mail text editor *SUCKS*!!!!

lol :p

I noticed something else regarding terminated processes that have never run and I’m not sure if that’s not a bug:
When I suspend a process (that has never run) that is not the active process, I can reliably reproduce that the entire #terminate method is being executed. The process’ suspendedContext is the bottom context (as it should be). However, the pc is equal to the startpc, since that process never had a chance to to anything. The result is that #isTerminated will answer false, even though the process is technically terminated.
One side effect of this is that it’s impossible to do something like “[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].” because that will not terminate for all processes. Luckily those processes can be garbage collected regardless of what #isTerminated says.

One obvious fix would be to set the pc of the suspendedContext to nil but I’m not sure that’s a good idea.

What do you think?

I think that's fine.

Cheers,
Max
Cheers,
Max
Cheers,
Max 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?

Cheers,
Max
-- 
best,
Eliot
-- 
best,
Eliot
-- 
best,
Eliot
--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Max Leske
and created a slice. I’d be grateful if you could take a look. There are three new tests that not only test #isTerminating but a lot of other expectations (like running the unwind blocks) too.

Cheers,
Max


On 22.09.2014, at 18:30, Eliot Miranda <[hidden email]> wrote:

Hi Max,

   phhh, that editor truncated my reply (that's my excuse and I'm sticking to it), so...

On Mon, Sep 22, 2014 at 4:57 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

Thanks a lot for those explanations.

On 18.09.2014, at 20:53, Eliot Miranda <[hidden email]> wrote:

Hi Max,

    phhh, time zone differences suck ;-)

On Thu, Sep 18, 2014 at 3:50 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

I can't see anything to do other than waiting.   One thing is to run the process at as close to user priority as possible, so I would say

proc := [ Semaphore new wait ] forkAt: Processor activePriority - 1.
 
Another important thing is that you're not giving your process a chance to run before you test for it not terminating.  So adding a yield after the first set of asserts and then repeating them is good:

started := false. proc := [ started := true. Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.

Another thing might be to boost its priority to make sure it finishes (except that that'll probably have no effect because IIRC right now the terminator runs the termination).  So you could say

proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.

process priority: Processor activePriority + 1.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].

Further I'd want to test that unwind blocks have been run so I'd say

testIsTerminated
| proc started unwound terminator |
unwound := false. proc := [   started := true. [Semaphore new wait]
ensure: [terminator := Processor activeProcess.
unwound := true] ]
forkAt: Processor activePriority - 1.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. "Alloc proc to run; there shouldnt be too much else going on so this delay should suffice"

self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
proc priority: Processor activePriority + 1. "This may have no effect; termination may be executed by the terminator rather than the terminatee; ys, this is a bug"
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
(Delay forMilliseconds: 10) wait. "Allow proc to terminate;  there shouldnt be too much else going on so this delay should suffice"

self assert: proc isTerminated.
self assert: proc isTerminating.
self assert: unwound.
self assert: terminator == proc. "But this should be made an expected failure; I don't know how to do that in SUnit…"

From your comments I expected this last statement to fail but actually it doesn’t. I guess that’s a good sign (?).


and google's mail text editor *SUCKS*!!!!

lol :p

I noticed something else regarding terminated processes that have never run and I’m not sure if that’s not a bug:
When I suspend a process (that has never run) that is not the active process, I can reliably reproduce that the entire #terminate method is being executed. The process’ suspendedContext is the bottom context (as it should be). However, the pc is equal to the startpc, since that process never had a chance to to anything. The result is that #isTerminated will answer false, even though the process is technically terminated.
One side effect of this is that it’s impossible to do something like “[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].” because that will not terminate for all processes. Luckily those processes can be garbage collected regardless of what #isTerminated says.

One obvious fix would be to set the pc of the suspendedContext to nil but I’m not sure that’s a good idea.

What do you think?

I think that's fine.

Cheers,
Max
Cheers,
Max
Cheers,
Max 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?

Cheers,
Max
-- 
best,
Eliot
-- 
best,
Eliot
-- 
best,
Eliot
--
best,
Eliot

Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Eliot Miranda-2


On Wed, Sep 24, 2014 at 2:58 AM, Max Leske <[hidden email]> wrote:
and created a slice. I’d be grateful if you could take a look. There are three new tests that not only test #isTerminating but a lot of other expectations (like running the unwind blocks) too.

excuse the stupid question but where's the source?
- How do I download a file containing the slice?  (a change set, .cs file?)
- How do I view the slice in the browser?
 

Cheers,
Max


On 22.09.2014, at 18:30, Eliot Miranda <[hidden email]> wrote:

Hi Max,

   phhh, that editor truncated my reply (that's my excuse and I'm sticking to it), so...

On Mon, Sep 22, 2014 at 4:57 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

Thanks a lot for those explanations.

On 18.09.2014, at 20:53, Eliot Miranda <[hidden email]> wrote:

Hi Max,

    phhh, time zone differences suck ;-)

On Thu, Sep 18, 2014 at 3:50 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

I can't see anything to do other than waiting.   One thing is to run the process at as close to user priority as possible, so I would say

proc := [ Semaphore new wait ] forkAt: Processor activePriority - 1.
 
Another important thing is that you're not giving your process a chance to run before you test for it not terminating.  So adding a yield after the first set of asserts and then repeating them is good:

started := false. proc := [ started := true. Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.

Another thing might be to boost its priority to make sure it finishes (except that that'll probably have no effect because IIRC right now the terminator runs the termination).  So you could say

proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.

process priority: Processor activePriority + 1.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].

Further I'd want to test that unwind blocks have been run so I'd say

testIsTerminated
| proc started unwound terminator |
unwound := false. proc := [   started := true. [Semaphore new wait]
ensure: [terminator := Processor activeProcess.
unwound := true] ]
forkAt: Processor activePriority - 1.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. "Alloc proc to run; there shouldnt be too much else going on so this delay should suffice"

self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
proc priority: Processor activePriority + 1. "This may have no effect; termination may be executed by the terminator rather than the terminatee; ys, this is a bug"
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
(Delay forMilliseconds: 10) wait. "Allow proc to terminate;  there shouldnt be too much else going on so this delay should suffice"

self assert: proc isTerminated.
self assert: proc isTerminating.
self assert: unwound.
self assert: terminator == proc. "But this should be made an expected failure; I don't know how to do that in SUnit…"

From your comments I expected this last statement to fail but actually it doesn’t. I guess that’s a good sign (?).


and google's mail text editor *SUCKS*!!!!

lol :p

I noticed something else regarding terminated processes that have never run and I’m not sure if that’s not a bug:
When I suspend a process (that has never run) that is not the active process, I can reliably reproduce that the entire #terminate method is being executed. The process’ suspendedContext is the bottom context (as it should be). However, the pc is equal to the startpc, since that process never had a chance to to anything. The result is that #isTerminated will answer false, even though the process is technically terminated.
One side effect of this is that it’s impossible to do something like “[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].” because that will not terminate for all processes. Luckily those processes can be garbage collected regardless of what #isTerminated says.

One obvious fix would be to set the pc of the suspendedContext to nil but I’m not sure that’s a good idea.

What do you think?

I think that's fine.

Cheers,
Max
Cheers,
Max
Cheers,
Max 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?

Cheers,
Max
-- 
best,
Eliot
-- 
best,
Eliot
-- 
best,
Eliot
--
best,
Eliot




--
best,
Eliot
Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

EstebanLM
is a SLICE in the Pharo40Inbox.
A SLICE is just a meta MCZ (A package who defines dependences). 
Url to get it is:


then just browse for the issue number: 14064

It will be called: SLICE-Issue-14064-SomethingElse

you can merge it without problems, but take into a account that  the issue needs a preload and a postload (scripts to execute before and after the merge). 

Preload: 

DangerousClassNotifier disable.

Postload: 

DangerousClassNotifier enable.



On 24 Sep 2014, at 18:08, Eliot Miranda <[hidden email]> wrote:



On Wed, Sep 24, 2014 at 2:58 AM, Max Leske <[hidden email]> wrote:
and created a slice. I’d be grateful if you could take a look. There are three new tests that not only test #isTerminating but a lot of other expectations (like running the unwind blocks) too.

excuse the stupid question but where's the source?
- How do I download a file containing the slice?  (a change set, .cs file?)
- How do I view the slice in the browser?
 

Cheers,
Max


On 22.09.2014, at 18:30, Eliot Miranda <[hidden email]> wrote:

Hi Max,

   phhh, that editor truncated my reply (that's my excuse and I'm sticking to it), so...

On Mon, Sep 22, 2014 at 4:57 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

Thanks a lot for those explanations.

On 18.09.2014, at 20:53, Eliot Miranda <[hidden email]> wrote:

Hi Max,

    phhh, time zone differences suck ;-)

On Thu, Sep 18, 2014 at 3:50 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

I can't see anything to do other than waiting.   One thing is to run the process at as close to user priority as possible, so I would say

proc := [ Semaphore new wait ] forkAt: Processor activePriority - 1.
 
Another important thing is that you're not giving your process a chance to run before you test for it not terminating.  So adding a yield after the first set of asserts and then repeating them is good:

started := false. proc := [ started := true. Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.

Another thing might be to boost its priority to make sure it finishes (except that that'll probably have no effect because IIRC right now the terminator runs the termination).  So you could say

proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.

process priority: Processor activePriority + 1.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].

Further I'd want to test that unwind blocks have been run so I'd say

testIsTerminated
| proc started unwound terminator |
unwound := false. proc := [   started := true. [Semaphore new wait]
ensure: [terminator := Processor activeProcess.
unwound := true] ]
forkAt: Processor activePriority - 1.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. "Alloc proc to run; there shouldnt be too much else going on so this delay should suffice"

self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
proc priority: Processor activePriority + 1. "This may have no effect; termination may be executed by the terminator rather than the terminatee; ys, this is a bug"
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
(Delay forMilliseconds: 10) wait. "Allow proc to terminate;  there shouldnt be too much else going on so this delay should suffice"

self assert: proc isTerminated.
self assert: proc isTerminating.
self assert: unwound.
self assert: terminator == proc. "But this should be made an expected failure; I don't know how to do that in SUnit…"

From your comments I expected this last statement to fail but actually it doesn’t. I guess that’s a good sign (?).


and google's mail text editor *SUCKS*!!!!

lol :p

I noticed something else regarding terminated processes that have never run and I’m not sure if that’s not a bug:
When I suspend a process (that has never run) that is not the active process, I can reliably reproduce that the entire #terminate method is being executed. The process’ suspendedContext is the bottom context (as it should be). However, the pc is equal to the startpc, since that process never had a chance to to anything. The result is that #isTerminated will answer false, even though the process is technically terminated.
One side effect of this is that it’s impossible to do something like “[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].” because that will not terminate for all processes. Luckily those processes can be garbage collected regardless of what #isTerminated says.

One obvious fix would be to set the pc of the suspendedContext to nil but I’m not sure that’s a good idea.

What do you think?

I think that's fine.

Cheers,
Max
Cheers,
Max
Cheers,
Max 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?

Cheers,
Max
-- 
best,
Eliot
-- 
best,
Eliot
-- 
best,
Eliot
--
best,
Eliot




--
best,
Eliot

Reply | Threaded
Open this post in threaded view
|

Re: I'm confused about Process>>isTerminated

Eliot Miranda-2


On Wed, Sep 24, 2014 at 9:14 AM, Esteban Lorenzano <[hidden email]> wrote:
is a SLICE in the Pharo40Inbox.
A SLICE is just a meta MCZ (A package who defines dependences). 

Cool, and /thanks/, but there should be a direct pointer to it from the Fogbugz page so it's easy to get to, no?

 
Url to get it is:


then just browse for the issue number: 14064

It will be called: SLICE-Issue-14064-SomethingElse

you can merge it without problems, but take into a account that  the issue needs a preload and a postload (scripts to execute before and after the merge). 

Preload: 

DangerousClassNotifier disable.

Postload: 

DangerousClassNotifier enable.



On 24 Sep 2014, at 18:08, Eliot Miranda <[hidden email]> wrote:



On Wed, Sep 24, 2014 at 2:58 AM, Max Leske <[hidden email]> wrote:
and created a slice. I’d be grateful if you could take a look. There are three new tests that not only test #isTerminating but a lot of other expectations (like running the unwind blocks) too.

excuse the stupid question but where's the source?
- How do I download a file containing the slice?  (a change set, .cs file?)
- How do I view the slice in the browser?
 

Cheers,
Max


On 22.09.2014, at 18:30, Eliot Miranda <[hidden email]> wrote:

Hi Max,

   phhh, that editor truncated my reply (that's my excuse and I'm sticking to it), so...

On Mon, Sep 22, 2014 at 4:57 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

Thanks a lot for those explanations.

On 18.09.2014, at 20:53, Eliot Miranda <[hidden email]> wrote:

Hi Max,

    phhh, time zone differences suck ;-)

On Thu, Sep 18, 2014 at 3:50 AM, Max Leske <[hidden email]> wrote:
Hi Eliot,

On 18.09.2014, at 01:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Wed, Sep 17, 2014 at 1:59 PM, Max Leske <[hidden email]> wrote:
Hi Eliot


On 16.09.2014, at 20:18, Eliot Miranda <[hidden email]> wrote:

Hi Max,

On Tue, Sep 16, 2014 at 11:05 AM, Max Leske <[hidden email]> wrote:
Hi

As always when I want to check if a process has died I get very confused by #isTerminated and I’m wondering if I just don’t get how it’s supposed to work or if there are others that share my confusion.

Old implementation:

isTerminated

        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
          or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                   If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                   from value and there is nothing more to do."
                suspendedContext isBottomContext
                and: [ suspendedContext pc > suspendedContext startpc ] ]


Pharo 4 implementation:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead not “<————————————————————————— new"
                and: [ suspendedContext pc > suspendedContext startpc ] ] ]


The old implementation would break if the suspended context was dead (i.e. the pc was nil) because the send of #> would produce an MNU.
The new implementation doesn’t fix that, even though it looks like it at first glance: if the pc is nil, the #> send will still happen -> MNU.

Off the top of my head it would seem that it should be isDead or: [] not isDead not and:

isTerminated
        self isActiveProcess ifTrue: [^ false].
        ^suspendedContext isNil
         or: ["If the suspendedContext is the bottomContext it is the block in Process>>newProcess.
                  If so, and the pc is greater than the startpc, the bock has alrteady sent and returned
                  from value and there is nothing more to do.”
                suspendedContext isBottomContext
                and: [ suspendedContext isDead
                          or: [ suspendedContext pc > suspendedContext startpc ] ] ] 

Phew. Glad you see that the same way.

isDead
        ^ pc isNil

and maybe (suspendedContext pc ifNil: [true] ifNotNil: [:pc| pc > suspendedContext startpc]) is more obvious.

Anyway, neither implementation will reliably tell me if the process has been terminated:
- an inactive process will be suspended when #terminate is sent and report that it has not been terminated (#isSuspended -> true, #isTerminated -> false)

except that it *hasn't* been terminated, it is merely in the process of termination.  It isn't terminated until all unwind blocks have run, right?

True. Easy to forget when you can just kill -9 on the console… :)

 
- a properly terminated process will raise an MNU (although apparently not always…?)

but that's a bug the change I suggested will fix.
 
- all the states in between: no clue

I would like to know two things:
1. how can I check if a process has already *received* a #terminate? (I would then assume that the process will die eventually)

I don't think you can without putting a critical section around terminate and adding some process-specific variable that is set when you send terminate.  termination is not instantaneous (unwind blocks have to be run), so it is potentially interruptible.

I’ve thought about this a bit. I wouldn’t really care if I don’t get a correct answer about the termination status immediately but I want to have it before the process terminates. In case of something like the following:

([ 10 seconds asDelay wait ] forkAt: 11) terminate

it can (potentially) take a very long time for the process to terminate. So if I have to poll 3 or 4 times that’s ok but I don’t want to wait for minutes.
One solution would be to take your idea of the variable, but without the critical block:

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating := true.  “<——————————————————————————————————— changed"
self isActiveProcess 
ifTrue: [
ctxt := thisContext.
[ ctxt := ctxt findNextUnwindContextUpTo: nil.
ctxt isNil ] whileFalse: 
[ (ctxt tempAt: 2) ifNil:
[ ctxt tempAt: 2 put: nil.
unwindBlock := ctxt tempAt: 1.
thisContext terminateTo: ctxt.
unwindBlock value ]].
thisContext terminateTo: nil.
self suspend ]
 ifFalse: [
"Always suspend the process first so it doesn't accidentally get woken up"
 oldList := self suspend.
suspendedContext ifNotNil:[
"Figure out if we are terminating the process while waiting in Semaphore>>critical:
In this case, pop the suspendedContext so that we leave the ensure: block inside
Semaphore>>critical: without signaling the semaphore."
(oldList class == Semaphore and:[
suspendedContext method == (Semaphore compiledMethodAt: #critical:)]) ifTrue:[
suspendedContext := suspendedContext home.].
  "If we are terminating a process halfways through an unwind, try to complete that unwind block first."
(suspendedContext findNextUnwindContextUpTo: nil) ifNotNil: [ :outer |
(suspendedContext findContextSuchThat: [ :c | c closure == (outer tempAt: 1)]) 
ifNotNil: [ :inner |
 "This is an unwind block currently under evaluation"
suspendedContext runUntilErrorOrReturnFrom: inner ]].
ctxt := self popTo: suspendedContext bottomContext.
ctxt == suspendedContext bottomContext ifFalse: [
self debug: ctxt title: 'Unwind error during termination']] ].



isTerminating
^ terminating ifNil: [ ^ false ]


With this small modification I can run the example from above and immediately see that it will die eventually.

I’m aware that one process might not see the change to the variable immediately but as I said, I wouldn’t really care.


What do you think?

 Yes that looks good.  But given that branches are atomic (ifTrue: is not a send) why not do

Process>>initialize
    terminating := false.

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [terminating := true].  
self isActiveProcess 
ifTrue:
...

?

I would suggest a status inst var, as in

Process>>initialize
    status := nil

terminate 
"Stop the process that the receiver represents forever.  Unwind to execute pending ensure:/ifCurtailed: blocks before terminating."

| ctxt unwindBlock oldList |
status == #terminating
ifTrue: [self error: 'Process is already terminated, or being terminated']
ifFalse: [status := terminating].  
self isActiveProcess 
ifTrue:
...

but the temptation then is to have lots of different status values and I'm leery of introducing that kind of complication without a strong justification.


I’ve worked a bit on an implementation along your suggestions. I wrote a test which looks like this:

testIsTerminated
| proc |
proc := [ Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].  “<——————————— ???"

self assert: proc isTerminated.
self assert: proc isTerminating

The test works AFAICT (apart from the loop…) but I want to also have a check after the process has terminated. Is there some reliable way to wait for a process to die? I tried something like this for example:

proc run.
self assert: proc isTerminated.

But that locks up the active process (obviously) until I interrupt it manually. If there is such a way, I could also add a method that lets a process x wait for the completion of a process y for example (or not, depending on how difficult it is :) )

I can't see anything to do other than waiting.   One thing is to run the process at as close to user priority as possible, so I would say

proc := [ Semaphore new wait ] forkAt: Processor activePriority - 1.
 
Another important thing is that you're not giving your process a chance to run before you test for it not terminating.  So adding a yield after the first set of asserts and then repeating them is good:

started := false. proc := [ started := true. Semaphore new wait ] forkAt: 30.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.

Another thing might be to boost its priority to make sure it finishes (except that that'll probably have no effect because IIRC right now the terminator runs the termination).  So you could say

proc terminate.
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.

process priority: Processor activePriority + 1.
[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].

Further I'd want to test that unwind blocks have been run so I'd say

testIsTerminated
| proc started unwound terminator |
unwound := false. proc := [   started := true. [Semaphore new wait]
ensure: [terminator := Processor activeProcess.
unwound := true] ]
forkAt: Processor activePriority - 1.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
(Delay forMilliseconds: 10) wait. "Alloc proc to run; there shouldnt be too much else going on so this delay should suffice"

self assert: started.
self deny: proc isSuspended.
self deny: proc isTerminating.
self deny: proc isTerminated.
proc terminate.
proc priority: Processor activePriority + 1. "This may have no effect; termination may be executed by the terminator rather than the terminatee; ys, this is a bug"
self deny: proc isTerminated.
self assert: proc isSuspended.
self assert: proc isTerminating.
(Delay forMilliseconds: 10) wait. "Allow proc to terminate;  there shouldnt be too much else going on so this delay should suffice"

self assert: proc isTerminated.
self assert: proc isTerminating.
self assert: unwound.
self assert: terminator == proc. "But this should be made an expected failure; I don't know how to do that in SUnit…"

From your comments I expected this last statement to fail but actually it doesn’t. I guess that’s a good sign (?).


and google's mail text editor *SUCKS*!!!!

lol :p

I noticed something else regarding terminated processes that have never run and I’m not sure if that’s not a bug:
When I suspend a process (that has never run) that is not the active process, I can reliably reproduce that the entire #terminate method is being executed. The process’ suspendedContext is the bottom context (as it should be). However, the pc is equal to the startpc, since that process never had a chance to to anything. The result is that #isTerminated will answer false, even though the process is technically terminated.
One side effect of this is that it’s impossible to do something like “[ proc isTerminated ] whileFalse: [ 1 second asDelay wait ].” because that will not terminate for all processes. Luckily those processes can be garbage collected regardless of what #isTerminated says.

One obvious fix would be to set the pc of the suspendedContext to nil but I’m not sure that’s a good idea.

What do you think?

I think that's fine.

Cheers,
Max
Cheers,
Max
Cheers,
Max 
2. how can I check if a process is *actually* dead? (in case a “half dead” process will still unwind or whatever)

see above.

What would be necessary to make those tests (or better ones) possible (rewrite the whole process implementation?)?

Cheers,
Max
-- 
best,
Eliot
-- 
best,
Eliot
-- 
best,
Eliot
--
best,
Eliot




--
best,
Eliot




--
best,
Eliot