[squeak-dev] The Trunk: Kernel-ar.237.mcz

Alexander Lazarević laza at blobworks.com
Sat Sep 5 06:43:02 UTC 2009


Hi Andreas!

I think it all stems from [1]. In short what I think happened was that
it was reported that very long delays (>SmallInt) made the image hang,
because a primitive would choke on not SmallInt parameters. I and
others just wanted to prevent this by just not allowing very long
delays and to have some LongDelay for very special use cases where
very long delays would be required. I think this was harvested and
made it into the image. There was also the idea of fixing the delay
code to have no artificial limit on delays and a change for
timeoutSemaphore:after: was proposed that juggled Delays to make long
Delays possible. This also went into the image some time, BUT the code
to not allow long delays was not removed. So I guess this code never
had an effect. Now it was you, if my memory serves me well, that
introduced handleTimerEvent et.al. which just naturally made long
delays possible. This also went into the image, BUT also having the
other fixes left in places. So I guess what was left was a mess of
three disjunct fixes for the same problem.

I will change the class comment of Delay that warns about too long
delays and remove the Test that checks for long delays to be refused
and now fails.

Alex

[1] http://bugs.squeak.org/view.php?id=854

On Fri, Sep 4, 2009 at 6:48 AM, <commits at source.squeak.org> wrote:
> Andreas Raab uploaded a new version of Kernel to project The Trunk:
> http://source.squeak.org/trunk/Kernel-ar.237.mcz
>
> ==================== Summary ====================
>
> Name: Kernel-ar.237
> Author: ar
> Time: 3 September 2009, 9:48:09 am
> UUID: 0ce8d553-42c8-2d42-add2-fbadccdbfe28
> Ancestors: Kernel-tfel.236
>
> http://bugs.squeak.org/view.php?id=7321
>
> Change Set:             DelayCleanup
> Date:                   23 March 2009
> Author:                 Andreas Raab
>
> Cleans up Delay by removing many of the no longer used methods (timerInterruptWatcher etc). It also provides some fixes for methods that got mysteriously broken even though their original versions were perfectly fine, including Delay class>>timeoutSemaphore:after:.
>
> =============== Diff against Kernel-tfel.236 ===============
>
> Item was changed:
> + ----- Method: Delay class>>primSignal:atMilliseconds: (in category 'primitives') -----
> - ----- Method: Delay class>>primSignal:atMilliseconds: (in category 'testing') -----
>  primSignal: aSemaphore atMilliseconds: aSmallInteger
>        "Signal the semaphore when the millisecond clock reaches the value of the second argument. Fail if the first argument is neither a Semaphore nor nil. Essential. See Object documentation whatIsAPrimitive."
> -
> -       | guardianDelay |
>        <primitive: 136>
> +       ^self primitiveFailed!
> -       "VM code actually only fails if the time parameter is not a SmallInteger value"
> -       aSmallInteger isInteger ifFalse:["somebody messed up badly and we can't do much about it"
> -               aSemaphore ifNotNil: [
> -                       ActiveDelay := nil.
> -                       aSemaphore signal. "Prevent an image crash"].
> -       ^self primitiveError: 'primSignal:atMilliseconds: failed because of a non-Integer resumption time parameter. The Semaphore has been signalled as a best guess of the right thing to do'].
> -
> -       "So now we feel fairly sure that the aSmallInteger resumption time is actually a large integer and we need to just wait some more. To make the system do that we need a fake Delay and a reasonable resumption time to feed to the VM. A decent value is SmallInteger maxVal since the VM handles correlating that sort of largish value and clock wrapping.
> -       First though we return the problem Delay to the queue"
> -       SuspendedDelays add: ActiveDelay.
> -       "Now we want a Delay set to fire and do nothing"
> -       guardianDelay := self guardianDelay.
> -       guardianDelay activate
> -       !
>
> Item was changed:
>  ----- Method: Delay class>>runTimerEventLoop (in category 'timer process') -----
>  runTimerEventLoop
>        "Run the timer event loop."
> +       [RunTimerEventLoop] whileTrue: [self handleTimerEvent]!
> -       [
> -               [RunTimerEventLoop] whileTrue: [self handleTimerEvent]
> -       ] on: Error do:[:ex|
> -               "Clear out the process so it does't get killed"
> -               TimerEventLoop := nil.
> -               "Launch the old-style interrupt watcher"
> -               self startTimerInterruptWatcher.
> -               "And pass the exception on"
> -               ex pass.
> -       ].!
>
> Item was changed:
>  ----- Method: Delay class>>restoreResumptionTimes (in category 'snapshotting') -----
>  restoreResumptionTimes
>        "Private!! Restore the resumption times of all scheduled Delays after a snapshot or clock roll-over. This method should be called only while the AccessProtect semaphore is held."
>
>        | newBaseTime |
>        newBaseTime := Time millisecondClockValue.
>        SuspendedDelays do: [:d | d adjustResumptionTimeOldBase: 0 newBase: newBaseTime].
>        ActiveDelay == nil ifFalse: [
>                ActiveDelay adjustResumptionTimeOldBase: 0 newBase: newBaseTime.
> +       ].
> -               ActiveDelay activate].
>  !
>
> Item was changed:
>  ----- Method: Delay class>>forMilliseconds: (in category 'instance creation') -----
> + forMilliseconds: anInteger
> - forMilliseconds: aNumber
>        "Return a new Delay for the given number of milliseconds. Sending 'wait' to this Delay will cause the sender's process to be suspended for approximately that length of time."
>
> +       anInteger < 0 ifTrue: [self error: 'delay times cannot be negative'].
> +       ^ self new
> +               setDelay: anInteger asInteger
> +               forSemaphore: Semaphore new
> -       ^ self new setDelay: aNumber forSemaphore: Semaphore new
>  !
>
> Item was changed:
>  ----- Method: Delay class>>startUp (in category 'snapshotting') -----
>  startUp
>        "Restart active delay, if any, when resuming a snapshot."
>
> +       DelaySuspended ifFalse:[^self error: 'Trying to activate Delay twice'].
> +       DelaySuspended := false.
>        self restoreResumptionTimes.
> -       ActiveDelay == nil ifFalse: [ActiveDelay activate].
>        AccessProtect signal.
>  !
>
> Item was changed:
>  ----- Method: Delay class>>startTimerEventLoop (in category 'timer process') -----
>  startTimerEventLoop
>        "Start the timer event loop"
>        "Delay startTimerEventLoop"
>        self stopTimerEventLoop.
> -       self stopTimerInterruptWatcher.
>        AccessProtect := Semaphore forMutualExclusion.
>        ActiveDelayStartTime := Time millisecondClockValue.
>        SuspendedDelays :=
>                Heap withAll: (SuspendedDelays ifNil:[#()])
>                        sortBlock: [:d1 :d2 | d1 resumptionTime <= d2 resumptionTime].
>        TimingSemaphore := Semaphore new.
>        RunTimerEventLoop := true.
>        TimerEventLoop := [self runTimerEventLoop] newProcess.
>        TimerEventLoop priority: Processor timingPriority.
>        TimerEventLoop resume.
>        TimingSemaphore signal. "get going"
>  !
>
> Item was changed:
>  ----- Method: Delay class>>timeoutSemaphore:afterMSecs: (in category 'instance creation') -----
>  timeoutSemaphore: aSemaphore afterMSecs: anInteger
>        "Create and schedule a Delay to signal the given semaphore when the given number of milliseconds has elapsed. Return the scheduled Delay. The timeout can be cancelled by sending 'unschedule' to this Delay."
>        "Details: This mechanism is used to provide a timeout when waiting for an external event, such as arrival of data over a network connection, to signal a semaphore. The timeout ensures that the semaphore will be signalled within a reasonable period of time even if the event fails to occur. Typically, the waiting process cancels the timeout request when awoken, then determines if the awaited event has actually occurred."
>
> +       anInteger < 0 ifTrue: [self error: 'delay times cannot be negative'].
> +       ^ (self new setDelay: anInteger forSemaphore: aSemaphore) schedule
> -       ^ (self forMilliseconds: anInteger) schedule
>  !
>
> Item was changed:
>  ----- Method: Delay class>>initialize (in category 'class initialization') -----
>  initialize
> +       "Delay initialize."
> -       "Delay initialize"
>        self startTimerEventLoop.!
>
> Item was changed:
>  ----- Method: Delay class>>shutDown (in category 'snapshotting') -----
>  shutDown
>        "Suspend the active delay, if any, before snapshotting. It will be reactived when the snapshot is resumed."
>        "Details: This prevents a timer interrupt from waking up the active delay in the midst snapshoting, since the active delay will be restarted when resuming the snapshot and we don't want to process the delay twice."
>
>        AccessProtect wait.
>        self primSignal: nil atMilliseconds: 0.
>        self saveResumptionTimes.
> +       DelaySuspended := true.!
> - !
>
> Item was added:
> + ----- Method: Delay>>printOn: (in category 'printing') -----
> + printOn: aStream
> +       super printOn: aStream.
> +       aStream nextPutAll: '('; print: delayDuration; nextPutAll: ' msecs'.
> +       beingWaitedOn ifTrue:[
> +               aStream nextPutAll: '; '; print: resumptionTime - Time millisecondClockValue; nextPutAll: ' msecs remaining'.
> +       ].
> +       aStream nextPutAll: ')'.!
>
> Item was changed:
>  ----- Method: Delay>>unschedule (in category 'private') -----
>  unschedule
> +       AccessProtect critical:[
> +               FinishedDelay := self.
> +               TimingSemaphore signal.
> +       ].!
> -       "Unschedule this Delay. Do nothing if it wasn't scheduled."
> -
> -       | done |
> -       TimerEventLoop ifNotNil:[^self unscheduleEvent].
> -       AccessProtect critical: [
> -               done := false.
> -               [done] whileFalse:
> -                       [SuspendedDelays remove: self ifAbsent: [done := true]].
> -               ActiveDelay == self ifTrue: [
> -                       SuspendedDelays isEmpty
> -                               ifTrue: [
> -                                       ActiveDelay := nil.
> -                                       ActiveDelayStartTime := nil]
> -                               ifFalse: [
> -                                       SuspendedDelays removeFirst activate]]].
> - !
>
> Item was changed:
>  ----- Method: Delay>>setDelay:forSemaphore: (in category 'private') -----
> + setDelay: millisecondCount forSemaphore: aSemaphore
> - setDelay: milliseconds forSemaphore: aSemaphore
>        "Private!! Initialize this delay to signal the given semaphore after the given number of milliseconds."
>
> +       delayDuration := millisecondCount.
> -       delayDuration := milliseconds asInteger.
> -       delayDuration < 0 ifTrue: [self error: 'delay times cannot be negative'].
> -       delayDuration > (SmallInteger maxVal // 2)
> -               ifTrue: [self error: 'delay times can''t be longer than about six days (', (SmallInteger maxVal // 2) printString , 'ms)'].
>        delaySemaphore := aSemaphore.
> +       beingWaitedOn := false.
> + !
> -       beingWaitedOn := false.!
>
> Item was changed:
>  ----- Method: Delay class>>forSeconds: (in category 'instance creation') -----
>  forSeconds: aNumber
> +       "Return a new Delay for the given number of seconds. Sending 'wait' to this Delay will cause the sender's process to be suspended for approximately that length of time."
> +
> +       aNumber < 0 ifTrue: [self error: 'delay times cannot be negative'].
> +       ^ self new
> +               setDelay: (aNumber * 1000) asInteger
> +               forSemaphore: Semaphore new
> -       ^ self forMilliseconds: aNumber * 1000
>  !
>
> Item was changed:
>  Object subclass: #Delay
>        instanceVariableNames: 'delayDuration resumptionTime delaySemaphore beingWaitedOn'
> +       classVariableNames: 'AccessProtect ActiveDelay ActiveDelayStartTime DelaySuspended FinishedDelay RunTimerEventLoop ScheduledDelay SuspendedDelays TimerEventLoop TimingSemaphore'
> -       classVariableNames: 'AccessProtect ActiveDelay ActiveDelayStartTime FinishedDelay RunTimerEventLoop ScheduledDelay SuspendedDelays TimerEventLoop TimingSemaphore'
>        poolDictionaries: ''
>        category: 'Kernel-Processes'!
>
>  !Delay commentStamp: 'stephaneducasse 10/1/2005 21:07' prior: 0!
>  I am the main way that a process may pause for some amount of time.  The simplest usage is like this:
>
>        (Delay forSeconds: 5) wait.
>
>  An instance of Delay responds to the message 'wait' by suspending the caller's process for a certain amount of time. The duration of the pause is specified when the Delay is created with the message forMilliseconds: or forSeconds:. A Delay can be used again when the current wait has finished. For example, a clock process might repeatedly wait on a one-second Delay.
>
>  The maximum delay is (SmallInteger maxVal // 2) milliseconds, or about six days. A delay in progress when an image snapshot is saved is resumed when the snapshot is re-started. Delays work across millisecond clock roll-overs.
>
>
>  For a more complex example, see  #testDelayOf:for:rect: .
>
>  A word of advice:
>  This is THE highest priority code which is run in Squeak, in other words it is time-critical. The speed of this code is critical for accurate responses, it is critical for network services, it affects every last part of the system.
>
>  In short: Don't fix it if it ain't broken!! This code isn't supposed to be beautiful, it's supposed to be fast!! The reason for duplicating code is to make it fast. The reason for not using ifNil:[]ifNotNil:[] is that the compiler may not inline those. Since the effect of changes are VERY hard to predict it is best to leave things as they are for now unless there is an actual need to change anything!
>
> Item was changed:
>  ----- Method: Delay>>schedule (in category 'private') -----
>  schedule
> +       "Schedule this delay"
> +       resumptionTime := Time millisecondClockValue + delayDuration.
> +       AccessProtect critical:[
> +               ScheduledDelay := self.
> +               TimingSemaphore signal.
> +       ].!
> -       "Private!! Schedule this Delay, but return immediately rather than waiting. The receiver's semaphore will be signalled when its delay duration has elapsed."
> -
> -       beingWaitedOn ifTrue: [self error: 'This Delay has already been scheduled.'].
> -
> -       TimerEventLoop ifNotNil:[^self scheduleEvent].
> -       AccessProtect critical: [
> -               beingWaitedOn := true.
> -               resumptionTime := Time millisecondClockValue + delayDuration.
> -               ActiveDelay == nil
> -                       ifTrue: [self activate]
> -                       ifFalse: [
> -                               resumptionTime < ActiveDelay resumptionTime
> -                                       ifTrue: [
> -                                               SuspendedDelays add: ActiveDelay.
> -                                               self activate]
> -                                       ifFalse: [SuspendedDelays add: self]]].
> - !
>
> Item was removed:
> - ----- Method: Delay>>scheduleEvent (in category 'private') -----
> - scheduleEvent
> -       "Schedule this delay"
> -       resumptionTime := Time millisecondClockValue + delayDuration.
> -       AccessProtect critical:[
> -               ScheduledDelay := self.
> -               TimingSemaphore signal.
> -       ].!
>
> Item was removed:
> - ----- Method: Delay>>activate (in category 'private') -----
> - activate
> -       "Private!! Make the receiver the Delay to be awoken when the next timer interrupt occurs. This method should only be called from a block protected by the AccessProtect semaphore."
> -       TimerEventLoop ifNotNil:[^nil].
> -       ActiveDelay := self.
> -       ActiveDelayStartTime := Time millisecondClockValue.
> -       ActiveDelayStartTime > resumptionTime ifTrue:[
> -               ActiveDelay signalWaitingProcess.
> -               SuspendedDelays isEmpty ifTrue:[
> -                       ActiveDelay := nil.
> -                       ActiveDelayStartTime := nil.
> -               ] ifFalse:[SuspendedDelays removeFirst activate].
> -       ] ifFalse:[
> -               TimingSemaphore initSignals.
> -               Delay primSignal: TimingSemaphore atMilliseconds: resumptionTime.
> -       ].!
>
> Item was removed:
> - ----- Method: Delay>>unscheduleEvent (in category 'private') -----
> - unscheduleEvent
> -       AccessProtect critical:[
> -               FinishedDelay := self.
> -               TimingSemaphore signal.
> -       ].!
>
> Item was removed:
> - ----- Method: Delay class>>startTimerInterruptWatcher (in category 'timer process') -----
> - startTimerInterruptWatcher
> -       "Reset the class variables that keep track of active Delays and re-start the timer interrupt watcher process. Any currently scheduled delays are forgotten."
> -       "Delay startTimerInterruptWatcher"
> -       | p |
> -       self stopTimerEventLoop.
> -       self stopTimerInterruptWatcher.
> -       TimingSemaphore := Semaphore new.
> -       AccessProtect := Semaphore forMutualExclusion.
> -       SuspendedDelays :=
> -               SortedCollection sortBlock:
> -                       [:d1 :d2 | d1 resumptionTime <= d2 resumptionTime].
> -       ActiveDelay := nil.
> -       p := [self timerInterruptWatcher] newProcess.
> -       p priority: Processor timingPriority.
> -       p resume.
> - !
>
> Item was removed:
> - ----- Method: Delay class>>guardianDelay (in category 'instance creation') -----
> - guardianDelay
> -       "Make a Delay with a resumption time far in the future but still a SmallInteger so that it can be used as a guardian for the active delay queue. No process will be waiting on this and when triggered it will do nothing. What it allows is very long Delays where the resumption time is a large integer; should such a delay get activated it will fail the primitive and we creat one of these guardians to make sure the delay timer keeps going and triggers the resumption time recalculations in save/restoreResumptionTime"
> -       ^self new beGuardianDelay!
>
> Item was removed:
> - ----- Method: Delay class>>stopTimerInterruptWatcher (in category 'timer process') -----
> - stopTimerInterruptWatcher
> -       "Reset the class variables that keep track of active Delays and re-start the timer interrupt watcher process. Any currently scheduled delays are forgotten."
> -       "Delay startTimerInterruptWatcher"
> -       self primSignal: nil atMilliseconds: 0.
> -       TimingSemaphore ifNotNil:[TimingSemaphore terminateProcess].!
>
> Item was removed:
> - ----- Method: Delay class>>timerInterruptWatcher (in category 'timer process') -----
> - timerInterruptWatcher
> -       "This loop runs in its own process. It waits for a timer interrupt and
> -       wakes up the active delay. Note that timer interrupts are only enabled
> -       when there are active delays."
> -       | nowTime |
> -       [true]
> -               whileTrue: [TimingSemaphore wait.
> -                       AccessProtect
> -                               critical: [ActiveDelay == nil
> -                                               ifFalse: [ActiveDelay signalWaitingProcess.
> -                                                       (nowTime := Time millisecondClockValue) < ActiveDelayStartTime
> -                                                               ifTrue: ["clock wrapped so adjust the resumption
> -                                                                       times of all the suspended delays. No
> -                                                                       point adjusting the active delay since
> -                                                                       we've just triggered it"
> -                                                                       SuspendedDelays
> -                                                                               do: [:d | d adjustResumptionTimeOldBase: ActiveDelayStartTime newBase: nowTime]]].
> -                                       SuspendedDelays isEmpty
> -                                               ifTrue: [ActiveDelay := nil.
> -                                                       ActiveDelayStartTime := nil]
> -                                               ifFalse: [SuspendedDelays removeFirst activate]]]!
>
> Item was removed:
> - ----- Method: Delay>>beGuardianDelay (in category 'private') -----
> - beGuardianDelay
> -       "see comment for class method guardianDelay"
> -       beingWaitedOn := false.
> -       resumptionTime := SmallInteger maxVal.
> -       delaySemaphore := Semaphore new!
>
>
>



More information about the Squeak-dev mailing list