ProcessorScheduler.st
changeset 1679 dbbfbd78b1e4
parent 1676 12b3b5dcf68f
child 1680 b90690d9d6c5
--- a/ProcessorScheduler.st	Mon Sep 23 15:25:39 1996 +0200
+++ b/ProcessorScheduler.st	Mon Sep 23 15:36:01 1996 +0200
@@ -10,6 +10,8 @@
  hereby transferred.
 "
 
+'From Smalltalk/X, Version:2.10.9 on 23-sep-1996 at 14:25:15'                   !
+
 Object subclass:#ProcessorScheduler
 	instanceVariableNames:'quiescentProcessLists scheduler zombie activeProcess
 		currentPriority readFdArray readSemaphoreArray readCheckArray
@@ -17,10 +19,11 @@
 		timeoutProcessArray timeoutSemaphoreArray idleActions anyTimeouts
 		dispatching interruptedProcess useIOInterrupts gotIOInterrupt
 		osChildExitActions gotChildSignalInterrupt
-		exitWhenNoMoreUserProcesses'
+		exitWhenNoMoreUserProcesses suspendScheduler'
 	classVariableNames:'KnownProcesses KnownProcessIds PureEventDriven
 		UserSchedulingPriority UserInterruptPriority TimingPriority
-		HighestPriority SchedulingPriority MaxNumberOfProcesses'
+		HighestPriority SchedulingPriority MaxNumberOfProcesses
+		InvalidProcessSignal'
 	poolDictionaries:''
 	category:'Kernel-Processes'
 !
@@ -74,58 +77,58 @@
 
     [class variables:]
 
-        KnownProcesses          <Collection>    all known processes
-        KnownProcessIds         <Collection>    and their IDs
+	KnownProcesses          <Collection>    all known processes
+	KnownProcessIds         <Collection>    and their IDs
 
-        PureEventDriven         <Boolean>       true, if no process support
-                                                is available
+	PureEventDriven         <Boolean>       true, if no process support
+						is available
 
-        UserSchedulingPriority  <Integer>       the priority at which normal
-                                                user interfaces run
+	UserSchedulingPriority  <Integer>       the priority at which normal
+						user interfaces run
 
-        UserInterruptPriority                   the priority at which user-
-                                                interrupts (Cntl-C) processing
-                                                takes place. Processes with
-                                                a greater or equal priority are
-                                                not interruptable.
+	UserInterruptPriority                   the priority at which user-
+						interrupts (Cntl-C) processing
+						takes place. Processes with
+						a greater or equal priority are
+						not interruptable.
 
-        TimingPriority                          the priority used for timing.
-                                                Processes with a greater or
-                                                equal priority are not interrupted
-                                                by timers.
+	TimingPriority                          the priority used for timing.
+						Processes with a greater or
+						equal priority are not interrupted
+						by timers.
 
-        HighestPriority                         The highest allowed prio for processes
+	HighestPriority                         The highest allowed prio for processes
 
-        SchedulingPriority                      The priority of the scheduler (must
-                                                me higher than any other).
+	SchedulingPriority                      The priority of the scheduler (must
+						me higher than any other).
 
-        MaxNumberOfProcesses                    if non-nil, no more than this
-                                                number of processes are allowed
-                                                (for debugging)
+	MaxNumberOfProcesses                    if non-nil, no more than this
+						number of processes are allowed
+						(for debugging)
 
     most interesting methods:
 
-        Processor>>suspend:                  (see also Process>>suspend)
-        Processor>>resume:                   (see also Process>>resume)
-        Processor>>terminate:                (see also Process>>terminate)
-        Processor>>yield 
-        Processor>>changePriority:for:       (see also Process>>priority:
+	Processor>>suspend:                  (see also Process>>suspend)
+	Processor>>resume:                   (see also Process>>resume)
+	Processor>>terminate:                (see also Process>>terminate)
+	Processor>>yield 
+	Processor>>changePriority:for:       (see also Process>>priority:
 
-        Processor>>signal:afterSeconds:      (see also Delay>>forSeconds:)
-        Processor>>signal:afterMilliseconds: (see also Delay>>forMilliseconds:)
-        Processor>>signal:onInput:           (see also ExternalStream>>readWait)
-        Processor>>signal:onOutput:          (see also ExternalStream>>writeWait)
-        Processor>>disableSemaphore:
+	Processor>>signal:afterSeconds:      (see also Delay>>forSeconds:)
+	Processor>>signal:afterMilliseconds: (see also Delay>>forMilliseconds:)
+	Processor>>signal:onInput:           (see also ExternalStream>>readWait)
+	Processor>>signal:onOutput:          (see also ExternalStream>>writeWait)
+	Processor>>disableSemaphore:
 
 
     [see also:]
-        Process
-        Delay Semaphore SemaphoreSet SharedQueue
-        WindowGroup
-        (``Working with processes'': programming/processes.html)
+	Process
+	Delay Semaphore SemaphoreSet SharedQueue
+	WindowGroup
+	(``Working with processes'': programming/processes.html)
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 ! !
 
@@ -141,6 +144,12 @@
     SchedulingPriority := 31.
     HighestPriority := 30.
 
+    InvalidProcessSignal isNil ifTrue:[
+        InvalidProcessSignal := ErrorSignal newSignalMayProceed:true.
+        InvalidProcessSignal nameClass:self message:#invalidProcessSignal.
+        InvalidProcessSignal notifierString:'invalid process'.
+    ].
+
     Processor isNil ifTrue:[
         "create the one and only processor"
 
@@ -156,6 +165,7 @@
     ].
 
     "Modified: 7.3.1996 / 19:22:49 / cg"
+    "Modified: 23.9.1996 / 14:24:50 / stefan"
 ! !
 
 !ProcessorScheduler  class methodsFor:'instance creation'!
@@ -166,6 +176,14 @@
     self error:'only one processor is allowed in the system'
 ! !
 
+!ProcessorScheduler  class methodsFor:'Signal constants'!
+
+invalidProcessSignal
+    ^ InvalidProcessSignal
+
+    "Created: 23.9.1996 / 13:44:57 / stefan"
+! !
+
 !ProcessorScheduler  class methodsFor:'instance release'!
 
 informDispose
@@ -513,7 +531,7 @@
      handle all timeout actions
     "
     anyTimeouts ifTrue:[
-        self evaluateTimeouts
+	self evaluateTimeouts
     ].
 
     "first do a quick check for semaphores using checkActions - this is needed for
@@ -523,24 +541,24 @@
     any := false.
     nActions := readCheckArray size.
     1 to:nActions do:[:index |
-        checkBlock := readCheckArray at:index.
-        (checkBlock notNil and:[checkBlock value]) ifTrue:[
-            sema := readSemaphoreArray at:index.
-            sema notNil ifTrue:[
-                sema signalOnce.
-            ].
-            any := true.
-        ]
+	checkBlock := readCheckArray at:index.
+	(checkBlock notNil and:[checkBlock value]) ifTrue:[
+	    sema := readSemaphoreArray at:index.
+	    sema notNil ifTrue:[
+		sema signalOnce.
+	    ].
+	    any := true.
+	]
     ].
 
     "now, someone might be runnable ..."
 
     p := self highestPriorityRunnableProcess.
     p isNil ifTrue:[
-        "/ no one runnable, hard wait for event or timeout
+	"/ no one runnable, hard wait for event or timeout
 
-        self waitForEventOrTimeout.
-        ^ self
+	self waitForEventOrTimeout.
+	^ self
     ].
 
     pri := p priority.
@@ -571,10 +589,10 @@
 
 "
     pri < TimingPriority ifTrue:[
-        anyTimeouts ifTrue:[
-            millis := self timeToNextTimeout.
-            millis == 0 ifTrue:[^ self].
-        ]
+	anyTimeouts ifTrue:[
+	    millis := self timeToNextTimeout.
+	    millis == 0 ifTrue:[^ self].
+	]
     ].
 "
 
@@ -587,30 +605,30 @@
     pri < UserInterruptPriority ifTrue:[
     
 "comment out this if above is uncommented"
-        anyTimeouts ifTrue:[
-            millis := self timeToNextTimeout.
-            millis == 0 ifTrue:[^ self].
-        ].
+	anyTimeouts ifTrue:[
+	    millis := self timeToNextTimeout.
+	    millis == 0 ifTrue:[^ self].
+	].
 "---"
 
-        useIOInterrupts ifTrue:[
-            readFdArray do:[:fd |
-                fd notNil ifTrue:[
-                    OperatingSystem enableIOInterruptsOn:fd
-                ].
-            ].
-        ] ifFalse:[
-            millis notNil ifTrue:[
-                millis := millis min:50
-            ] ifFalse:[
-                millis := 50
-            ]
-        ]
+	useIOInterrupts ifTrue:[
+	    readFdArray do:[:fd |
+		fd notNil ifTrue:[
+		    OperatingSystem enableIOInterruptsOn:fd
+		].
+	    ].
+	] ifFalse:[
+	    millis notNil ifTrue:[
+		millis := millis min:50
+	    ] ifFalse:[
+		millis := 50
+	    ]
+	]
     ].
 
     millis notNil ifTrue:[
-        "schedule a clock interrupt after millis milliseconds"
-        OperatingSystem enableTimer:millis rounded.
+	"schedule a clock interrupt after millis milliseconds"
+	OperatingSystem enableTimer:millis rounded.
     ].
 
     "
@@ -620,24 +638,24 @@
     self threadSwitch:p.
 
     "... when we arrive here, we are back on stage.
-         Either by an ALARM or IO signal, or by a suspend of another process
+	 Either by an ALARM or IO signal, or by a suspend of another process
     "
 
     millis notNil ifTrue:[
-        OperatingSystem disableTimer.
+	OperatingSystem disableTimer.
     ].
 
     "/ check for OS process termination
     gotChildSignalInterrupt ifTrue:[
-        gotChildSignalInterrupt := false.
-        self handleChildSignalInterrupt
+	gotChildSignalInterrupt := false.
+	self handleChildSignalInterrupt
     ].
 
     "/ check for new input
 
     (gotIOInterrupt or:[useIOInterrupts not]) ifTrue:[
-        gotIOInterrupt := false.
-        self checkForInputWithTimeout:0.
+	gotIOInterrupt := false.
+	self checkForInputWithTimeout:0.
     ]
 
     "Modified: 12.4.1996 / 10:14:18 / stefan"
@@ -662,20 +680,20 @@
     dispatchAction := [self dispatch].
 
     handlerAction := [:ex |
-			'PROCESSOR: ignored signal' infoPrintNL.
-			ex return
-		     ].
+                        ('PROCESSOR: ignored signal (', ex signal printString, ')') infoPrintNL.
+                        ex return
+                     ].
 
     ignoredSignals := SignalSet 
-			with:(Process terminateSignal)
-			with:AbortSignal.
+                        with:(Process terminateSignal)
+                        with:AbortSignal.
 
     "/
     "/ I made this an extra call to dispatch; this allows recompilation
     "/  of the dispatch-handling code in the running system.
     "/
     [dispatching] whileTrue:[
-	ignoredSignals handle:handlerAction do:dispatchAction
+        ignoredSignals handle:handlerAction do:dispatchAction
     ].
 
     "/ we arrive here in standalone Apps,
@@ -685,6 +703,7 @@
     'PROCESSOR: finish dispatch (no more processes)' infoPrintNL.
 
     "Modified: 22.12.1995 / 23:12:51 / cg"
+    "Modified: 23.9.1996 / 14:19:56 / stefan"
 !
 
 exitWhenNoMoreUserProcesses:aBoolean
@@ -715,37 +734,37 @@
     "/ no interrupt processing, to avoid races with monitorPid
     wasBlocked := OperatingSystem blockInterrupts.
     [
-        [
-            osProcessStatus := OperatingSystem childProcessWait:blocking.
-            osProcessStatus notNil ifTrue:[
-                |pid action|
+	[
+	    osProcessStatus := OperatingSystem childProcessWait:blocking.
+	    osProcessStatus notNil ifTrue:[
+		|pid action|
 
-                pid := osProcessStatus pid.
-                osProcessStatus stillAlive ifTrue:[
-                    action := osChildExitActions at:pid ifAbsent:[].
-                ] ifFalse:[
-                    action := osChildExitActions removeKey:pid ifAbsent:[].
-                ].
-                action notNil ifTrue:[
-                    action value:osProcessStatus
-                ].
-            ].
+		pid := osProcessStatus pid.
+		osProcessStatus stillAlive ifTrue:[
+		    action := osChildExitActions at:pid ifAbsent:[].
+		] ifFalse:[
+		    action := osChildExitActions removeKey:pid ifAbsent:[].
+		].
+		action notNil ifTrue:[
+		    action value:osProcessStatus
+		].
+	    ].
 
-            "/ if pollChildProcesses does block, poll only one status change.
-            "/ we will get another SIGCHLD for other status changes.
+	    "/ if pollChildProcesses does block, poll only one status change.
+	    "/ we will get another SIGCHLD for other status changes.
 
-            osProcessStatus notNil and:[blocking not]
-        ] whileTrue.
+	    osProcessStatus notNil and:[blocking not]
+	] whileTrue.
 
-        "/ if there are no more waiters, disable SIGCHILD handler.
-        "/ this helps us with synchronous waiters (e.g. pclose),
-        "/ But they should block SIGCHLD anyway.
+	"/ if there are no more waiters, disable SIGCHILD handler.
+	"/ this helps us with synchronous waiters (e.g. pclose),
+	"/ But they should block SIGCHLD anyway.
 
-        osChildExitActions isEmpty ifTrue:[
-            OperatingSystem disableChildSignalInterrupts.
-        ].
+	osChildExitActions isEmpty ifTrue:[
+	    OperatingSystem disableChildSignalInterrupts.
+	].
     ] valueNowOrOnUnwindDo:[
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ]
 
     "Modified: 5.1.1996 / 16:56:11 / stefan"
@@ -760,23 +779,23 @@
     "
 
     OperatingSystem sigCHLD ~= 0 ifTrue:[
-        "/ SIGCHLD is supported,
-        "/ aBlock will be evaluated, as soon as a SIGCHLD interrupt for pid has been received.
-        OperatingSystem enableChildSignalInterrupts.
-        osChildExitActions at:pid put:aBlock
+	"/ SIGCHLD is supported,
+	"/ aBlock will be evaluated, as soon as a SIGCHLD interrupt for pid has been received.
+	OperatingSystem enableChildSignalInterrupts.
+	osChildExitActions at:pid put:aBlock
     ] ifFalse:[
-        |osProcessStatus|
-        "/ SIGCHLD is not supported, wait synchronously for the exit
-        "/ of pid.
-        [
-            osProcessStatus := OperatingSystem childProcessWait:true.
-            osProcessStatus notNil ifTrue:[
-                (osProcessStatus pid = pid) ifTrue:[
-                    aBlock value:osProcessStatus.
-                ].
-                osProcessStatus stillAlive
-            ].
-        ] whileTrue.
+	|osProcessStatus|
+	"/ SIGCHLD is not supported, wait synchronously for the exit
+	"/ of pid.
+	[
+	    osProcessStatus := OperatingSystem childProcessWait:true.
+	    osProcessStatus notNil ifTrue:[
+		(osProcessStatus pid = pid) ifTrue:[
+		    aBlock value:osProcessStatus.
+		].
+		osProcessStatus stillAlive
+	    ].
+	] whileTrue.
     ].
 
     "Created: 28.12.1995 / 14:22:10 / stefan"
@@ -801,10 +820,10 @@
      and, make the process runnable
     "
     aProcess state ~~ #stopped ifTrue:[
-        "
-         and, make the process runnable
-        "
-        self resume:aProcess
+	"
+	 and, make the process runnable
+	"
+	self resume:aProcess
     ]
 
     "Modified: 17.6.1996 / 14:40:52 / cg"
@@ -854,9 +873,9 @@
     extern OBJ ___threadSwitch();
 
     if (__isSmallInteger(id)) {
-        ok = ___threadSwitch(__context, __intVal(id), (singleStep == true) ? 1 : 0);
+	ok = ___threadSwitch(__context, __intVal(id), (singleStep == true) ? 1 : 0);
     } else {
-        ok = false;
+	ok = false;
     }
 %}.
     "time passes spent in some other process ...
@@ -867,24 +886,24 @@
     currentPriority := oldProcess priority.
 
     ok ifFalse:[
-        "
-         switch failed for some reason -
-         destroy the bad process
-        "
-        p id ~~ 0 ifTrue:[
-            'PROCESSOR: problem with process ' errorPrint. 
-                p id errorPrint. 
-                p name notNil ifTrue:[
-                    ' (' errorPrint. p name errorPrint. ')' errorPrint.
-                ].
-                '; hard-terminate it.' errorPrintNL.
-            p state:#suspended.
-            self terminateNoSignal:p.
-        ]
+	"
+	 switch failed for some reason -
+	 destroy the bad process
+	"
+	p id ~~ 0 ifTrue:[
+	    'PROCESSOR: problem with process ' errorPrint. 
+		p id errorPrint. 
+		p name notNil ifTrue:[
+		    ' (' errorPrint. p name errorPrint. ')' errorPrint.
+		].
+		'; hard-terminate it.' errorPrintNL.
+	    p state:#suspended.
+	    self terminateNoSignal:p.
+	]
     ].
     zombie notNil ifTrue:[
-        self class threadDestroy:zombie.
-        zombie := nil
+	self class threadDestroy:zombie.
+	zombie := nil
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 ! !
@@ -954,9 +973,9 @@
      p l|
 
     KnownProcesses isNil ifTrue:[
-        KnownProcesses := WeakArray new:10.
-        KnownProcesses watcher:self class.
-        KnownProcessIds := OrderedCollection new.
+	KnownProcesses := WeakArray new:10.
+	KnownProcesses watcher:self class.
+	KnownProcessIds := OrderedCollection new.
     ].
 
     "
@@ -1117,15 +1136,15 @@
     listArray := quiescentProcessLists.
 
     [prio >= 1] whileTrue:[
-        l := listArray at:prio.
-        l notNil ifTrue:[
-            l do:[:aProcess |
-                aProcess processGroupId ~~ 0 ifTrue:[
-                    ^ true.
-                ]
-            ]
-        ].
-        prio := prio - 1
+	l := listArray at:prio.
+	l notNil ifTrue:[
+	    l do:[:aProcess |
+		aProcess processGroupId ~~ 0 ifTrue:[
+		    ^ true.
+		]
+	    ]
+	].
+	prio := prio - 1
     ].
     ^ false
 
@@ -1144,22 +1163,22 @@
     prio := HighestPriority.
     listArray := quiescentProcessLists.
     [prio >= 1] whileTrue:[
-        l := listArray at:prio.
-        l notNil ifTrue:[
-            l notEmpty ifTrue:[
-                p := l first.
-                "
-                 if it got corrupted somehow ...
-                "
-                p id isNil ifTrue:[
-                    'PROCESSOR: process with nil id removed' errorPrintNL.
-                    l removeFirst.
-                    ^ nil.
-                ].
-                ^ p
-            ]
-        ].
-        prio := prio - 1
+	l := listArray at:prio.
+	l notNil ifTrue:[
+	    l notEmpty ifTrue:[
+		p := l first.
+		"
+		 if it got corrupted somehow ...
+		"
+		p id isNil ifTrue:[
+		    'PROCESSOR: process with nil id removed' errorPrintNL.
+		    l removeFirst.
+		    ^ nil.
+		].
+		^ p
+	    ]
+	].
+	prio := prio - 1
     ].
     ^ nil
 
@@ -1190,9 +1209,9 @@
     (PureEventDriven 
     or:[aProcess id == 0
     or:[(Display notNil and:[Display dispatchProcess == aProcess])
-        " nameOrId endsWith:'dispatcher' "
+	" nameOrId endsWith:'dispatcher' "
     ]]) ifTrue:[
-        ^ true
+	^ true
     ].
     ^ false
 
@@ -1219,46 +1238,46 @@
     "
     newPrio := prio.
     newPrio < 1 ifTrue:[
-        newPrio := 1.
+	newPrio := 1.
     ] ifFalse:[
-        newPrio > HighestPriority ifTrue:[
-            newPrio := HighestPriority
-        ]
+	newPrio > HighestPriority ifTrue:[
+	    newPrio := HighestPriority
+	]
     ].
 
     [
-        wasBlocked := OperatingSystem blockInterrupts.
+	wasBlocked := OperatingSystem blockInterrupts.
 
-        aProcess setPriority:newPrio.
+	aProcess setPriority:newPrio.
 
-        oldList := quiescentProcessLists at:oldPrio.
-        oldList notNil ifTrue:[
-            (oldList identityIndexOf:aProcess) ~~ 0 ifTrue:[
-                oldList remove:aProcess.
+	oldList := quiescentProcessLists at:oldPrio.
+	oldList notNil ifTrue:[
+	    (oldList identityIndexOf:aProcess) ~~ 0 ifTrue:[
+		oldList remove:aProcess.
 
-                newList := quiescentProcessLists at:newPrio.
-                newList isNil ifTrue:[
-                    quiescentProcessLists at:newPrio put:(newList := LinkedList new).
-                ].
-                newList addLast:aProcess.
+		newList := quiescentProcessLists at:newPrio.
+		newList isNil ifTrue:[
+		    quiescentProcessLists at:newPrio put:(newList := LinkedList new).
+		].
+		newList addLast:aProcess.
 
-                "if its the current process lowering its prio 
-                 or another one raising, we have to reschedule"
+		"if its the current process lowering its prio 
+		 or another one raising, we have to reschedule"
 
-                aProcess == activeProcess ifTrue:[
-                    currentPriority := newPrio.
-                    newPrio < oldPrio ifTrue:[
-                        self threadSwitch:scheduler.    
-                    ]
-                ] ifFalse:[
-                    newPrio > currentPriority ifTrue:[
-                        self threadSwitch:aProcess.
-                    ]
-                ].
-            ].
-        ]
+		aProcess == activeProcess ifTrue:[
+		    currentPriority := newPrio.
+		    newPrio < oldPrio ifTrue:[
+			self threadSwitch:scheduler.    
+		    ]
+		] ifFalse:[
+		    newPrio > currentPriority ifTrue:[
+			self threadSwitch:aProcess.
+		    ]
+		].
+	    ].
+	]
     ] valueNowOrOnUnwindDo:[
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
     ]
 
     "Modified: 29.7.1996 / 12:11:57 / cg"
@@ -1294,10 +1313,17 @@
 
     |l pri wasBlocked|
 
-    (aProcess isNil or:[aProcess == activeProcess]) ifTrue:[^ self].
+    "ignore, if process is already dead"
+    (aProcess isNil or:[aProcess id isNil]) ifTrue:[^ self].
+
 
-    "ignore, if process is already dead"
-    aProcess id isNil ifTrue:[^ self].
+    aProcess == activeProcess ifTrue:[
+	"special handling for waiting schedulers"
+	aProcess == scheduler ifTrue:[
+	    suspendScheduler := false.
+	].
+	^ self
+    ].
 
     wasBlocked := OperatingSystem blockInterrupts.
 
@@ -1306,27 +1332,27 @@
     l := quiescentProcessLists at:pri.
     "if already running, ignore"
     l notNil ifTrue:[
-        (l identityIndexOf:aProcess) ~~ 0 ifTrue:[
-            wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-            ^ self
-        ]
+	(l identityIndexOf:aProcess) ~~ 0 ifTrue:[
+	    wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	    ^ self
+	]
     ] ifFalse:[
-        l := LinkedList new.
-        quiescentProcessLists at:pri put:l.
+	l := LinkedList new.
+	quiescentProcessLists at:pri put:l.
     ].
     l addLast:aProcess.
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
     (pri > currentPriority) ifTrue:[
-        "
-         its prio is higher; immediately transfer control to it
-        "
-        self threadSwitch:aProcess
+	"
+	 its prio is higher; immediately transfer control to it
+	"
+	self threadSwitch:aProcess
     ] ifFalse:[
-        "
-         its prio is lower; it will have to wait for a while ...
-        "
-        aProcess state:#run 
+	"
+	 its prio is lower; it will have to wait for a while ...
+	"
+	aProcess state:#run 
     ]
 
     "Modified: 29.7.1996 / 12:07:37 / cg"
@@ -1353,16 +1379,25 @@
      some debugging stuff
     "
     aProcess isNil ifTrue:[
-        MiniDebugger enterWithMessage:'PROCESSOR: nil suspend'.
+        InvalidProcessSignal raiseWith:aProcess errorString:'PROCESSOR: nil suspend'.
         ^ self
     ].
     aProcess id isNil ifTrue:[
-        MiniDebugger enterWithMessage:'PROCESSOR: bad suspend: already dead'.
+        InvalidProcessSignal raiseWith:aProcess errorString:'PROCESSOR: bad suspend: already dead'.
         self threadSwitch:scheduler.
         ^ self
     ].
     aProcess == scheduler ifTrue:[
-        MiniDebugger enterWithMessage:'PROCESSOR: scheduler should never be suspended'.
+        "only scheduler may suspend itself"
+        activeProcess == scheduler ifTrue:[
+            suspendScheduler := true.
+            [suspendScheduler] whileTrue:[
+                self dispatch.
+            ].
+            ^ self
+        ].
+
+        InvalidProcessSignal raiseWith:aProcess errorString:'PROCESSOR: scheduler should never be suspended'.
         ^ self
     ].
 
@@ -1394,8 +1429,8 @@
         self threadSwitch:p 
     ].
 
-    "Modified: 13.12.1995 / 13:32:11 / stefan"
     "Modified: 29.7.1996 / 11:52:16 / cg"
+    "Modified: 23.9.1996 / 13:49:24 / stefan"
 !
 
 terminate:aProcess
@@ -1436,7 +1471,7 @@
 
     aProcess isNil ifTrue:[^ self].
     aProcess == scheduler ifTrue:[
-        MiniDebugger enterWithMessage:'PROCESSOR: I will not terminate scheduler'.
+        InvalidProcessSignal raiseWith:aProcess errorString:'PROCESSOR: I will not terminate scheduler'.
         ^ self
     ].
 
@@ -1476,6 +1511,7 @@
     ^ self
 
     "Modified: 29.7.1996 / 11:56:08 / cg"
+    "Modified: 23.9.1996 / 13:50:24 / stefan"
 !
 
 yield
@@ -1491,8 +1527,8 @@
      debugging consistency check - will be removed later
     "
     activeProcess priority ~~ currentPriority ifTrue:[
-        'PROCESSOR: oops - process changed priority' errorPrintNL.
-        currentPriority := activeProcess priority.
+	'PROCESSOR: oops - process changed priority' errorPrintNL.
+	currentPriority := activeProcess priority.
     ].
 
     l := quiescentProcessLists at:currentPriority.
@@ -1502,25 +1538,25 @@
      debugging consistency checks - will be removed later
     "
     sz == 0 ifTrue:[
-        wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
-        'PROCESSOR: oops - empty runnable list' errorPrintNL.
-        ^ self
+	wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
+	'PROCESSOR: oops - empty runnable list' errorPrintNL.
+	^ self
     ].
 
     "
      check if the running process is not the only one
     "
     sz ~~ 1 ifTrue:[
-        "
-         bring running process to the end
-        "
-        l removeFirst.
-        l addLast:activeProcess.
+	"
+	 bring running process to the end
+	"
+	l removeFirst.
+	l addLast:activeProcess.
 
-        "
-         and switch to first in the list
-        "
-        self threadSwitch:(l first).
+	"
+	 and switch to first in the list
+	"
+	self threadSwitch:(l first).
     ].
     wasBlocked ifFalse:[OperatingSystem unblockInterrupts].
 
@@ -1959,35 +1995,35 @@
     |fd index sema action|
 
     fd := OperatingSystem 
-              selectOnAnyReadable:readFdArray 
-                         writable:writeFdArray
-                        exception:nil 
-                      withTimeOut:millis.
+	      selectOnAnyReadable:readFdArray 
+			 writable:writeFdArray
+			exception:nil 
+		      withTimeOut:millis.
 
     fd isNil ifTrue:[
-        (OperatingSystem lastErrorSymbol == #EBADF) ifTrue:[
+	(OperatingSystem lastErrorSymbol == #EBADF) ifTrue:[
 
-            "/ mhmh - one of the fd's given to me is corrupt.
-            "/ find out which one .... and remove it
+	    "/ mhmh - one of the fd's given to me is corrupt.
+	    "/ find out which one .... and remove it
 
-            OperatingSystem clearLastErrorNumber.
-            self removeCorruptedFds
-        ]
+	    OperatingSystem clearLastErrorNumber.
+	    self removeCorruptedFds
+	]
     ] ifFalse:[
-        index := readFdArray indexOf:fd.
-        index ~~ 0 ifTrue:[
-            sema := readSemaphoreArray at:index.
-            sema notNil ifTrue:[
-                sema signalOnce.
-                ^ true
-            ] ifFalse:[
-                action := readCheckArray at:index.
-                action notNil ifTrue:[
-                    action value.
-                     ^ true
-                ]
-            ]
-        ]
+	index := readFdArray indexOf:fd.
+	index ~~ 0 ifTrue:[
+	    sema := readSemaphoreArray at:index.
+	    sema notNil ifTrue:[
+		sema signalOnce.
+		^ true
+	    ] ifFalse:[
+		action := readCheckArray at:index.
+		action notNil ifTrue:[
+		    action value.
+		     ^ true
+		]
+	    ]
+	]
     ].
     ^ false
 
@@ -2016,43 +2052,43 @@
       readFdArray/writeFdArray in the debugger)"
 
     readFdArray keysAndValuesDo:[:idx :fd |
-        |rslt sema|
+	|rslt sema|
 
-        rslt := OperatingSystem
-                    selectOnAnyReadable:(Array with:fd)
-                               writable:nil
-                              exception:nil
-                            withTimeOut:0.
+	rslt := OperatingSystem
+		    selectOnAnyReadable:(Array with:fd)
+			       writable:nil
+			      exception:nil
+			    withTimeOut:0.
 
-        (rslt isNil and:[OperatingSystem lastErrorSymbol == #EBADF]) ifTrue:[
-            ('PROCESSOR: removing invalid read fileDescriptor: ' , fd printString) errorPrintNL.
-            readFdArray at:idx put:nil.
-            OperatingSystem clearLastErrorNumber.
-            (sema := readSemaphoreArray at:idx) notNil ifTrue:[
-                readSemaphoreArray at:idx put:nil.
-                sema signal.
-            ].
-        ]
+	(rslt isNil and:[OperatingSystem lastErrorSymbol == #EBADF]) ifTrue:[
+	    ('PROCESSOR: removing invalid read fileDescriptor: ' , fd printString) errorPrintNL.
+	    readFdArray at:idx put:nil.
+	    OperatingSystem clearLastErrorNumber.
+	    (sema := readSemaphoreArray at:idx) notNil ifTrue:[
+		readSemaphoreArray at:idx put:nil.
+		sema signal.
+	    ].
+	]
     ].
 
     writeFdArray keysAndValuesDo:[:idx :fd |
-        |rslt sema|
+	|rslt sema|
 
-        rslt := OperatingSystem
-                    selectOnAnyReadable:nil
-                               writable:(Array with:fd)
-                              exception:nil
-                            withTimeOut:0.
+	rslt := OperatingSystem
+		    selectOnAnyReadable:nil
+			       writable:(Array with:fd)
+			      exception:nil
+			    withTimeOut:0.
 
-        (rslt isNil and:[OperatingSystem lastErrorSymbol == #EBADF]) ifTrue:[
-            ('PROCESSOR: removing invalid write fileDescriptor: ' , fd printString) errorPrintNL.
-            writeFdArray at:idx put:nil.
-            OperatingSystem clearLastErrorNumber.
-            (sema := writeSemaphoreArray at:idx) notNil ifTrue:[
-                writeSemaphoreArray at:idx put:nil.
-                sema signal.
-            ].
-        ]
+	(rslt isNil and:[OperatingSystem lastErrorSymbol == #EBADF]) ifTrue:[
+	    ('PROCESSOR: removing invalid write fileDescriptor: ' , fd printString) errorPrintNL.
+	    writeFdArray at:idx put:nil.
+	    OperatingSystem clearLastErrorNumber.
+	    (sema := writeSemaphoreArray at:idx) notNil ifTrue:[
+		writeSemaphoreArray at:idx put:nil.
+		sema signal.
+	    ].
+	]
     ].
 
     "Modified: 12.4.1996 / 09:32:58 / stefan"
@@ -2116,77 +2152,77 @@
 
     doingGC := true.
     [doingGC] whileTrue:[
-        anyTimeouts ifTrue:[
-            millis := self timeToNextTimeout.
-            (millis notNil and:[millis <= 0]) ifTrue:[
-                ^ self    "oops - hurry up checking"
-            ].
-        ].
+	anyTimeouts ifTrue:[
+	    millis := self timeToNextTimeout.
+	    (millis notNil and:[millis <= 0]) ifTrue:[
+		^ self    "oops - hurry up checking"
+	    ].
+	].
 
-        "
-         if its worth doing, collect a bit of garbage;
-         but not, if a backgroundCollector is active
-        "
-        ObjectMemory backgroundCollectorRunning ifTrue:[
-            doingGC := false
-        ] ifFalse:[
-            doingGC := ObjectMemory gcStepIfUseful.
-        ].
+	"
+	 if its worth doing, collect a bit of garbage;
+	 but not, if a backgroundCollector is active
+	"
+	ObjectMemory backgroundCollectorRunning ifTrue:[
+	    doingGC := false
+	] ifFalse:[
+	    doingGC := ObjectMemory gcStepIfUseful.
+	].
 
-        "then do idle actions"
-        (idleActions notNil and:[idleActions size ~~ 0]) ifTrue:[
-            idleActions do:[:aBlock |
-                aBlock value.
-            ].
-            ^ self   "go back checking"
-        ].
+	"then do idle actions"
+	(idleActions notNil and:[idleActions size ~~ 0]) ifTrue:[
+	    idleActions do:[:aBlock |
+		aBlock value.
+	    ].
+	    ^ self   "go back checking"
+	].
 
-        doingGC ifTrue:[
-            (self checkForInputWithTimeout:0) ifTrue:[
-                ^ self  "go back checking"
-            ]
-        ]
+	doingGC ifTrue:[
+	    (self checkForInputWithTimeout:0) ifTrue:[
+		^ self  "go back checking"
+	    ]
+	]
     ].
 
     exitWhenNoMoreUserProcesses ifTrue:[
-        "/ check if there are any processes at all
-        "/ stop dispatching if there is none
-        "/ (and millis is nil, which means that no timeout blocks are present)
-        "/ and no readSemaphores are present (which means that noone is waiting for input)
-        "/ and no writeSemaphores are present
+	"/ check if there are any processes at all
+	"/ stop dispatching if there is none
+	"/ (and millis is nil, which means that no timeout blocks are present)
+	"/ and no readSemaphores are present (which means that noone is waiting for input)
+	"/ and no writeSemaphores are present
 
-        anySema := false.
-        anySema := (readSemaphoreArray findFirst:[:sema | sema notNil]) ~~ 0.
-        anySema ifFalse:[
-            anySema := (writeSemaphoreArray findFirst:[:sema | sema notNil]) ~~ 0.
-        ].
-        anySema ifFalse:[
-            self anyUserProcessAtAll ifFalse:[
-                dispatching := false.
-                ^ self
-            ]
-        ].
+	anySema := false.
+	anySema := (readSemaphoreArray findFirst:[:sema | sema notNil]) ~~ 0.
+	anySema ifFalse:[
+	    anySema := (writeSemaphoreArray findFirst:[:sema | sema notNil]) ~~ 0.
+	].
+	anySema ifFalse:[
+	    self anyUserProcessAtAll ifFalse:[
+		dispatching := false.
+		^ self
+	    ]
+	].
     ].
 
     "/
     "/ absolutely nothing to do - simply wait
     "/
     OperatingSystem supportsSelect ifFalse:[
-        "SCO instant ShitStation has a bug here,
-         waiting always 1 sec in the select - therefore we delay a bit and
-         return - effectively polling in 50ms cycles
-        "
-        (self checkForInputWithTimeout:0) ifTrue:[
-            ^ self  "go back checking"
-        ].
-        OperatingSystem millisecondDelay:50.
-        ^ self
+	"SCO instant ShitStation has a bug here,
+	 waiting always 1 sec in the select - therefore we delay a bit and
+	 return - effectively polling in 50ms cycles
+	"
+	(self checkForInputWithTimeout:0) ifTrue:[
+	    ^ self  "go back checking"
+	].
+	OperatingSystem millisecondDelay:50.
+	^ self
     ].
 
     millis isNil ifTrue:[
-        millis := 9999.
+	millis := 9999.
     ] ifFalse:[
-        millis := millis rounded
+	millis := millis rounded
     ].
     self checkForInputWithTimeout:millis
 
@@ -2197,6 +2233,6 @@
 !ProcessorScheduler  class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ProcessorScheduler.st,v 1.90 1996-09-23 12:40:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ProcessorScheduler.st,v 1.91 1996-09-23 13:36:01 stefan Exp $'
 ! !
 ProcessorScheduler initialize!