[comp.lang.smalltalk] anyone using time-sliced scheduling w/st80?

huggins@ticipa.ti.com (Gray Huggins) (03/12/91)

We are considering modifying the appearance of how Smalltalk 80
schedules, from a priority only basis to priority and time-sliced.
Has anybody done any research on this topic?  Specifically, we have
more than one independent application that we want to run with equal
priority in the same image.

Thanks,
--
Gray Huggins                   Internet: huggins@ticipa.csc.ti.com
Texas Instruments                                          
PO Box 655012  M/S 3635        TI MSG:  GHUG
Dallas, TX 75265               Voice:   (214) 917-2202

csq031@umaxc.weeg.uiowa.edu (03/13/91)

You can implement your own scheduler on top of (or beside, as it were) of
the regular scheduler.  All you have to do is to install a tick handler
that runs at highest priority.  When it resumes, check to see if the currently
running process is one of the ones you're scheduling.  If it is, and its tick
has expired then you can suspend it and put it on your ready queue, and
resume the process you think should run next.

Better yet, study the scheduler code with the browser.  You might be able
to just wade in there and make what you want to happen happen.  Be advised
that you are guaranteed to hose the system with great frequency if you
muck around with the scheduler very much!


--
             Kent Williams --- williams@umaxc.weeg.uiowa.edu 
"'Is this heaven?' --- 'No, this is Iowa'" - from the movie "Field of Dreams"
"This isn't heaven, ... this is Cleveland" - Harry Allard, in "The Stupids Die"

huba@ls5.informatik.uni-dortmund.de (Hubert Baumeister) (03/14/91)

In article <4861@ns-mx.uiowa.edu>, csq031@umaxc.weeg.uiowa.edu writes:
|> You can implement your own scheduler on top of (or beside, as it were) of
|> the regular scheduler.  All you have to do is to install a tick handler
|> that runs at highest priority.  When it resumes, check to see if the currently
|> running process is one of the ones you're scheduling.  If it is, and its tick
|> has expired then you can suspend it and put it on your ready queue, and
|> resume the process you think should run next.
|> 
|> Better yet, study the scheduler code with the browser.  You might be able
|> to just wade in there and make what you want to happen happen.  Be advised
|> that you are guaranteed to hose the system with great frequency if you
|> muck around with the scheduler very much!
|> 
|> 
|> --
|>              Kent Williams --- williams@umaxc.weeg.uiowa.edu 
|> "'Is this heaven?' --- 'No, this is Iowa'" - from the movie "Field of Dreams"
|> "This isn't heaven, ... this is Cleveland" - Harry Allard, in "The Stupids Die"

I have hacked a short example how time slicing could be done is the spirit
of the above message. The basics is a high priority process that wakes up every
few milliseconds and regroups the processes in the waiting queue of the
highest priority that has more than one process.

To see how it works evaluate first
	| queue |
	ProcessorScheduler stopTimeSlicing. 
	queue := SharedQueue new.	
	[100 timesRepeat: [queue nextPut: 1]] fork.
	[100 timesRepeat: [queue nextPut: 2]] fork.
	queue inspect
In the contents of queue you will find first all the 1's and then all the
2's. If you then evaluate
	| queue |
	ProcessorScheduler startTimeSlicing. 
	queue := SharedQueue new.	
	[100 timesRepeat: [queue nextPut: 1]] fork.
	[100 timesRepeat: [queue nextPut: 2]] fork.
	queue inspect
then the 1's and 2's are mixed.

But notice that time slicing is dangerous in the current implementation of the
Smalltalk user interface as shows following example:
	ProcessorScheduler startTimeSlicing. 
	[100 timesRepeat: [Transcript show: 'Process 1';cr]] fork.
	[100 timesRepeat: [Transcript show: 'Process 2';cr]] fork.
This will hang up Smalltalk because some recources are not protected against
multiple access. (This is why the example above uses a SharedQueue instead of
a WriteStream)

The following example was written using Smalltalk Release 4.0 but it should
also work on previous releases.

---------------------------- cut here ---------------------------------

ProcessorScheduler class
	instanceVariableNames: ''!

ProcessorScheduler class organization changeFromString: '(''class initialization'' #initialize)
(''instance creation'' #new #new:with:)
(''background process'' #background:)
(''time slice process'' #example #startTimeSlicing #stopTimeSlicing)
'!

!ProcessorScheduler methodsFor: 'process state change'!

slice
	"Give other Processes at the current priority a chance to run."

	| i list |
	i := self highestPriority.
	[i>0 and: [(quiescentProcessLists at: i) size <= 1]]
	whileTrue: [i := i-1].
	i = 0 ifTrue: [^self].
	list := (quiescentProcessLists at: i).
	list addLast: list removeFirst.! !


!ProcessorScheduler class methodsFor: 'time slice process'!

startTimeSlicing
	"self startTimeSlicing"
	TimeSliceProcess notNil ifTrue: [^self].
	TimeSliceProcess := [[true] whileTrue: [(Delay forMilliseconds: 5) wait. Processor slice]] newProcess.
	TimeSliceProcess priority: (Processor highestPriority).
	TimeSliceProcess resume.! !


!ProcessorScheduler class methodsFor: 'time slice process'!

stopTimeSlicing
	"self stopTimeSlicing"

	TimeSliceProcess notNil
		ifTrue: 
			[TimeSliceProcess terminate.
			TimeSliceProcess := nil]! !


!ProcessorScheduler class methodsFor: 'time slice process'!

example
	"self stopTimeSlicing. 
	self example inspect"
	"self startTimeSlicing. 
	self example inspect"

	| queue |
	queue := SharedQueue new.
	[100 timesRepeat: [queue nextPut: 1]] fork.
	[100 timesRepeat: [queue nextPut: 2]] fork.
	^queue! !

winfwrd@dutrun.UUCP (Paul van der Weerd) (03/18/91)

The warning from Hubert Baumeister:

>But notice that time slicing is dangerous in the current implementation of the
>Smalltalk user interface as shows following example:
>        ProcessorScheduler startTimeSlicing.
>        [100 timesRepeat: [Transcript show: 'Process 1';cr]] fork.
>        [100 timesRepeat: [Transcript show: 'Process 2';cr]] fork.
>This will hang up Smalltalk because some recources are not protected against
>multiple access. (This is why the example above uses a SharedQueue instead of
>a WriteStream)

To prevent unprotected simultaneous access to a single Transcript, I took the
following approach:
(
| p1 p2 t1 t2 |
"Define some textcollectors."
[t1 := TextCollector new.
TextCollectorView open: t1 label: 'Process 1'] fork.
[t2 := TextCollector new.
TextCollectorView open: t2 label: 'Process 2'] fork.
"Define some processess."
p1 := [[true] whileTrue: [t1 show: 'A']] newProcess.
p2 := [[true] whileTrue: [t2 show: 'B']] newProcess.
"Run processes alternately."
(p1 priority: 3) resume.
(p2 priority: 3) resume.
300 timesRepeat: [
(Delay forMilliseconds: 200) wait.
(Processor suspendFirstAt: 3) resume].
p1 terminate.
p2 terminate.
)
Normally this works, but when some windows are overlapping,
the system crashes. What is wrong?

Question: A forked process is simple to create, but how do
you stop it without the process handle? Is something like a
ProcessInspector available?

--
Paul van der Weerd                  Tel. +31 15 782523
Delft University of Technology      Fax. +31 15 786522
Dept. of Computer Science           Email winfwrd@dutrun.tudelft.nl
Julianalaan 132
2628 BL  Delft
The Netherlands
...................................................................

huba@ls5.informatik.uni-dortmund.de (Hubert Baumeister) (03/19/91)

In article <15113@dutrun.UUCP>, winfwrd@dutrun.UUCP (Paul van der Weerd) writes:
 ...

|> To prevent unprotected simultaneous access to a single Transcript, I took the
|> following approach:
|> (
|> | p1 p2 t1 t2 |
|> "Define some textcollectors."
|> [t1 := TextCollector new.
|> TextCollectorView open: t1 label: 'Process 1'] fork.
|> [t2 := TextCollector new.
|> TextCollectorView open: t2 label: 'Process 2'] fork.
|> "Define some processess."
|> p1 := [[true] whileTrue: [t1 show: 'A']] newProcess.
|> p2 := [[true] whileTrue: [t2 show: 'B']] newProcess.
|> "Run processes alternately."
|> (p1 priority: 3) resume.
|> (p2 priority: 3) resume.
|> 300 timesRepeat: [
|> (Delay forMilliseconds: 200) wait.
|> (Processor suspendFirstAt: 3) resume].
|> p1 terminate.
|> p2 terminate.
|> )
|> Normally this works, but when some windows are overlapping,
|> the system crashes. What is wrong?

I suppose you use Smalltalk 80 v2.5 or earlier. These versions assume that
when drawing on a window this window is completely visible. To achieve this the
TextCollectorViews use the method displaySafe: aBlock in ControlManager. This
method tops the window and executes aBlock.
When both TextCollectorViews want to display themselves at the same time
there is a race condition in displaySafe:.

In Smalltalk Release 4.0 this works fine since there it is possible to draw on
partly hidden windows and thus it needs no hack like the one described above.

Hubert Baumeister
(huba@ls5.informatik.uni-dortmund.de)

hmm@julien.informatik.uni-dortmund.de (Hans Martin Mosner) (03/22/91)

For a customer project, we have implemented more priority levels and
timeslicing in PPS Smalltalk-80 release 2.3 and 2.5.  For the user
interface code and other things to keep working, the priority levels
UserSchedulingPriority and above must not be timesliced.  So we lifted
them and introduced a number of background priorities in addition to
UserBackgroundPriority.  Processes at these priority are regularly put
at the end of their respective scheduling queues by a high-priority
process (I think we currently have slices of 200 msecs or so).  Doing
the priority level extension is a bit tricky, but the timeslicing in
itself is very straightforward.
Of course you need something like the "Good Citizenry" code by PPS
so that the background processes can run at all, but we had that in
the images anyway.

Hans-Martin

winfwrd@dutrun.UUCP (Paul van der Weerd) (03/22/91)

In article <3109@laura.UUCP>, huba@ls5.informatik.uni-dortmund.de,
(Hubert Baumeister) writes:
>...
>I suppose you use Smalltalk 80 v2.5 or earlier. These versions assume that
>when drawing on a window this window is completely visible. To achieve this the
>TextCollectorViews use the method displaySafe: aBlock in ControlManager. This
>method tops the window and executes aBlock.
>When both TextCollectorViews want to display themselves at the same time
>there is a race condition in displaySafe:.

Indeed the ControlManager gets lost (Smalltalk-80 v2.5). So I extended the
example with extra protection:

| p1 p2 t1 t2 displayMutex |
"Protect the display code."
displayMutex _ Semaphore forMutualExclusion.
"Define some textcollectors."
[t1 := TextCollector new.
TextCollectorView open: t1 label: 'Process 1'] fork.
[t2 := TextCollector new.
TextCollectorView open: t2 label: 'Process 2'] fork.
"Define some processess."
p1 := [[true] whileTrue:
	[displayMutex critical: [t1 show: 'A']]] newProcess.
p2 := [[true] whileTrue:
	[displayMutex critical: [t2 show: 'B']]] newProcess.
"Run processes alternately."
(p1 priority: 3) resume.
(p2 priority: 3) resume.
300 timesRepeat: [
(Delay forMilliseconds: 200) wait.
(Processor suspendFirstAt: 3) resume].
p1 terminate.
p2 terminate.

This works fine. Also the appearance of the display during execution is okay.

Hubert Continues:
>In Smalltalk Release 4.0 this works fine since there it is possible to draw on
>partly hidden windows and thus it needs no hack like the one described above.

Hearing the word "hack" I added a classVariable DisplayMutex to
StandardSystemView and changed the class initialization method in:

!StandardSystemView class methodsFor: 'class initialization'!

initialize

	FillInHoles _ true.
	DisplayMutex _ Semaphore forMutualExclusion! !

This also works fine (no loss of control), but the display becomes a mess
during execution (use restore display afterwards).
Is this the kind of hack you had in mind?

--
Paul van der Weerd                  Tel. +31 15 782523
Delft University of Technology      Fax. +31 15 786522
Dept. of Computer Science           Email winfwrd@dutrun.tudelft.nl
Julianalaan 132
2628 BL  Delft
The Netherlands
...................................................................