care for homeless (non-top) views when assigning the focus
authorClaus Gittinger <cg@exept.de>
Thu, 24 Sep 1998 12:02:31 +0200
changeset 2363 e456e5040a57
parent 2362 e391d80efdb5
child 2364 50a217088763
care for homeless (non-top) views when assigning the focus (as in fileBrowsers kill button)
WGroup.st
WindowGroup.st
--- a/WGroup.st	Thu Sep 24 12:01:42 1998 +0200
+++ b/WGroup.st	Thu Sep 24 12:02:31 1998 +0200
@@ -263,31 +263,31 @@
     activeProcess := Processor activeProcess.
     " caching the last value ..."
     activeProcess == LastActiveProcess ifTrue:[
-        LastActiveGroup process == LastActiveProcess ifTrue:[
-            ^ LastActiveGroup
-        ]
+	LastActiveGroup process == LastActiveProcess ifTrue:[
+	    ^ LastActiveGroup
+	]
     ].
 
     wg := WindowGroupQuerySignal raise.
 
     wg isNil ifTrue:[
-        "/ mhmh - noone willing to answer that question ...
-        "/ (how can this happen ?)
-        groups := self scheduledWindowGroups 
-                    select:[:wg | wg process == activeProcess].
-        groups size == 1 ifTrue:[
-            wg := groups anElement
-        ] ifFalse:[
-            wg := groups detect:[:wg | wg isModal] ifNone:nil.
-            wg isNil ifTrue:[
-                wg := groups anElement
-            ]
-        ].
+	"/ mhmh - noone willing to answer that question ...
+	"/ (how can this happen ?)
+	groups := self scheduledWindowGroups 
+		    select:[:wg | wg process == activeProcess].
+	groups size == 1 ifTrue:[
+	    wg := groups anElement
+	] ifFalse:[
+	    wg := groups detect:[:wg | wg isModal] ifNone:nil.
+	    wg isNil ifTrue:[
+		wg := groups anElement
+	    ]
+	].
     ].
 
     wg notNil ifTrue:[
-        LastActiveProcess := activeProcess.
-        LastActiveGroup := wg.
+	LastActiveProcess := activeProcess.
+	LastActiveGroup := wg.
     ].
     ^ wg
 
@@ -356,34 +356,34 @@
     |dev|
 
     topViews notNil ifTrue:[
-        topViews do:[:v |
-            |app|
+	topViews do:[:v |
+	    |app|
 
-            (app := v application) notNil ifTrue:[
-                "/
-                "/ ok, it has an application;
-                "/ ask it for preferences.
-                "/
-                (dev := app graphicsDevice) notNil ifTrue:[
-                    ^ dev
-                ]
-            ].
-            (dev := v graphicsDevice) notNil ifTrue:[
-                ^ dev
-            ]
-        ]
+	    (app := v application) notNil ifTrue:[
+		"/
+		"/ ok, it has an application;
+		"/ ask it for preferences.
+		"/
+		(dev := app graphicsDevice) notNil ifTrue:[
+		    ^ dev
+		]
+	    ].
+	    (dev := v graphicsDevice) notNil ifTrue:[
+		^ dev
+	    ]
+	]
     ].
     views notNil ifTrue:[
-        views do:[:v |
-            (dev := v graphicsDevice) notNil ifTrue:[
-                ^ dev
-            ]
-        ]
+	views do:[:v |
+	    (dev := v graphicsDevice) notNil ifTrue:[
+		^ dev
+	    ]
+	]
     ].
     "/ ask the previousGroup; I could be a popUp-views group,
     "/ which has already closed its views (and is performing its action)
     previousGroup notNil ifTrue:[
-        ^ previousGroup graphicsDevice
+	^ previousGroup graphicsDevice
     ].
     ^ nil
 
@@ -454,9 +454,9 @@
     "return the windowGroups process"
 
     myProcess isNil ifTrue:[
-        previousGroup notNil ifTrue:[
-            ^ previousGroup process
-        ]
+	previousGroup notNil ifTrue:[
+	    ^ previousGroup process
+	]
     ].
     ^ myProcess
 
@@ -918,168 +918,168 @@
      and aBlock evaluates to true.
 
      Some signals are caught & handled: 
-        LeaveSignal forces an exit from the eventLoop;
-        AbortSignal brings us back into the loop, processing the next event;
-        ActivityNotifications send a #showActivity: if nonModal, 
-        otherwise they are ignored."
+	LeaveSignal forces an exit from the eventLoop;
+	AbortSignal brings us back into the loop, processing the next event;
+	ActivityNotifications send a #showActivity: if nonModal, 
+	otherwise they are ignored."
 
     |thisProcess sigs mainSema prevSema|
 
     thisProcess := Processor activeProcess.
 
     sigs := SignalSet 
-                with:AbortSignal 
-                with:LeaveSignal 
-                with:(self class activityNotificationSignal).
+		with:AbortSignal 
+		with:LeaveSignal 
+		with:(self class activityNotificationSignal).
 
     [
-        |p g s mainGroup mySema waitSema groupForSema|
+	|p g s mainGroup mySema waitSema groupForSema|
 
-        waitSema := mySema := mySensor eventSemaphore.
+	waitSema := mySema := mySensor eventSemaphore.
 
-        isModal ifTrue:[
-            mainGroup := self mainGroup.
-            mainGroup == self ifTrue:[
-                mainGroup := nil
-            ].
-        ] ifFalse:[
-            mainGroup := previousGroup
-        ].
+	isModal ifTrue:[
+	    mainGroup := self mainGroup.
+	    mainGroup == self ifTrue:[
+		mainGroup := nil
+	    ].
+	] ifFalse:[
+	    mainGroup := previousGroup
+	].
         
-        mainGroup notNil ifTrue:[
-            mainSema := mainGroup sensor eventSemaphore.
-            waitSema := SemaphoreSet with:mySema with:mainSema.
+	mainGroup notNil ifTrue:[
+	    mainSema := mainGroup sensor eventSemaphore.
+	    waitSema := SemaphoreSet with:mySema with:mainSema.
 
-            "/ must also care for all other groups in between
-            "/ (in case its a modal dialog opened from a modal dialog)
+	    "/ must also care for all other groups in between
+	    "/ (in case its a modal dialog opened from a modal dialog)
         
-            g := previousGroup.
-            g ~~ mainGroup ifTrue:[
-                groupForSema := IdentityDictionary new.
-                [g ~~ mainGroup] whileTrue:[
-                    s := g sensor eventSemaphore.
-                    waitSema add:s.
-                    groupForSema at:s put:g.
-                    g := g previousGroup.
-                ]
-            ].
-        ].
+	    g := previousGroup.
+	    g ~~ mainGroup ifTrue:[
+		groupForSema := IdentityDictionary new.
+		[g ~~ mainGroup] whileTrue:[
+		    s := g sensor eventSemaphore.
+		    waitSema add:s.
+		    groupForSema at:s put:g.
+		    g := g previousGroup.
+		]
+	    ].
+	].
 
-        [aBlock value] whileTrue:[ 
-            LastActiveGroup := self.
-            LastActiveProcess := thisProcess.
+	[aBlock value] whileTrue:[ 
+	    LastActiveGroup := self.
+	    LastActiveProcess := thisProcess.
 
-            (views isNil and:[topViews isNil]) ifTrue:[
-                myProcess notNil ifTrue:[
-                    p := myProcess.
-                    myProcess := nil.
-                    p terminate.
-                    "not reached - there is no life after death"
-                ].
-                "
-                 this is the end of a modal loop
-                 (not having a private process ...)
-                "
-                ^ self
-            ].
+	    (views isNil and:[topViews isNil]) ifTrue:[
+		myProcess notNil ifTrue:[
+		    p := myProcess.
+		    myProcess := nil.
+		    p terminate.
+		    "not reached - there is no life after death"
+		].
+		"
+		 this is the end of a modal loop
+		 (not having a private process ...)
+		"
+		^ self
+	    ].
 
-            sigs handle:[:ex |
-                |theSig|
+	    sigs handle:[:ex |
+		|theSig|
 
-                (theSig := ex signal) == AbortSignal ifTrue:[
-                    "/
-                    "/ on abort, stay in loop
-                    "/
-                    ex return
-                ].
-                theSig == LeaveSignal ifTrue:[
-                    "/
-                    "/ on leave, exit the event loop
-                    "/
-                    ^ self
-                ].
+		(theSig := ex signal) == AbortSignal ifTrue:[
+		    "/
+		    "/ on abort, stay in loop
+		    "/
+		    ex return
+		].
+		theSig == LeaveSignal ifTrue:[
+		    "/
+		    "/ on leave, exit the event loop
+		    "/
+		    ^ self
+		].
 
-                "/ ActivityNotification
-                "/
-                "/ if I am a modal-group, let it be handled
-                "/ by the outer main-groups handler
-                "/ otherwise show the activityMessage and continue.
-                "/
-                isModal ifTrue:[
-                    ex reject
-                    "never reached"
-                ].
-                self showActivity:(ex errorString).
-                ex proceed.
-            ] do:[
-                |dev gotSema mainView|
+		"/ ActivityNotification
+		"/
+		"/ if I am a modal-group, let it be handled
+		"/ by the outer main-groups handler
+		"/ otherwise show the activityMessage and continue.
+		"/
+		isModal ifTrue:[
+		    ex reject
+		    "never reached"
+		].
+		self showActivity:(ex errorString).
+		ex proceed.
+	    ] do:[
+		|dev gotSema mainView|
 
-                "/ Flush device output before going to sleep. 
-                "/ This may produce more events to arrive.
-                "/ Q: is this still needed (see suspendAction) ?
+		"/ Flush device output before going to sleep. 
+		"/ This may produce more events to arrive.
+		"/ Q: is this still needed (see suspendAction) ?
 
 "/                dev := self graphicsDevice.
 "/                dev notNil ifTrue:[dev flush].
 
-                "/ now, wait for an event to arrive
-                thisProcess setStateTo:#eventWait if:#active.
-                waitSema isNil ifTrue:[
-                    "/ oops - how can this happen ....
-                    ^ self.
-                ].
-                gotSema := waitSema wait.
-                LastActiveGroup := self.
-                LastActiveProcess := thisProcess.
+		"/ now, wait for an event to arrive
+		thisProcess setStateTo:#eventWait if:#active.
+		waitSema isNil ifTrue:[
+		    "/ oops - how can this happen ....
+		    ^ self.
+		].
+		gotSema := waitSema wait.
+		LastActiveGroup := self.
+		LastActiveProcess := thisProcess.
 
-                "/ some bad guy ;-) could have closed all down
-                "/ in the meanwhile ...
+		"/ some bad guy ;-) could have closed all down
+		"/ in the meanwhile ...
 
-                mySensor notNil ifTrue:[
-                    gotSema == mySema ifTrue:[
-                        "/
-                        "/ an event for me 
-                        "/
-                        self processEventsWithModalGroup:nil
-                    ] ifFalse:[
-                        groupForSema notNil ifTrue:[
-                            g := groupForSema at:gotSema ifAbsent:nil.
-                            g := g ? mainGroup.
-                        ] ifFalse:[
-                            g := mainGroup
-                        ].
+		mySensor notNil ifTrue:[
+		    gotSema == mySema ifTrue:[
+			"/
+			"/ an event for me 
+			"/
+			self processEventsWithModalGroup:nil
+		    ] ifFalse:[
+			groupForSema notNil ifTrue:[
+			    g := groupForSema at:gotSema ifAbsent:nil.
+			    g := g ? mainGroup.
+			] ifFalse:[
+			    g := mainGroup
+			].
 
-                        "/
-                        "/ an event for my mainGroup 
-                        "/
-                        g topViews notNil ifTrue:[
-                            mainView := g topViews first
-                        ].
-                        mainView notNil ifTrue:[
-                            "/
-                            "/ if anything happened to the mainGroup
-                            "/ bring my own topView back to the front
-                            "/ This keeps modalBoxes visible
-                            "/
-                            (g sensor hasConfigureEventFor:mainView) ifTrue:[
-                                topViews size > 0 ifTrue:[
-                                    topViews first raiseDeiconified
-                                ]
-                            ]
-                        ].
-                        "
-                         if modal, also check for redraw events in my maingroup
-                         (we arrive here after we woke up on maingroup sensor eventSemaphore)
-                        "
-                        g processEventsWithModalGroup:self.
-                    ]
-                ]
-            ].
-        ].
+			"/
+			"/ an event for my mainGroup 
+			"/
+			g topViews notNil ifTrue:[
+			    mainView := g topViews first
+			].
+			mainView notNil ifTrue:[
+			    "/
+			    "/ if anything happened to the mainGroup
+			    "/ bring my own topView back to the front
+			    "/ This keeps modalBoxes visible
+			    "/
+			    (g sensor hasConfigureEventFor:mainView) ifTrue:[
+				topViews size > 0 ifTrue:[
+				    topViews first raiseDeiconified
+				]
+			    ]
+			].
+			"
+			 if modal, also check for redraw events in my maingroup
+			 (we arrive here after we woke up on maingroup sensor eventSemaphore)
+			"
+			g processEventsWithModalGroup:self.
+		    ]
+		]
+	    ].
+	].
     ] valueNowOrOnUnwindDo:[
-        "/
-        "/ perform any cleanupActions
-        "/
-        cleanupActions notNil ifTrue:[cleanupActions value]
+	"/
+	"/ perform any cleanupActions
+	"/
+	cleanupActions notNil ifTrue:[cleanupActions value]
     ]
 
     "Modified: / 14.12.1995 / 11:12:24 / stefan"
@@ -1116,39 +1116,39 @@
 
     [mySensor notNil
      and:[(event := mySensor nextEvent) notNil]] whileTrue:[
-        ignore := false.
-        focus := focusView.
-        modalDelegate := false.
+	ignore := false.
+	focus := focusView.
+	modalDelegate := false.
 
-        modalGroup notNil ifTrue:[
-            "/ an incoming event for a masterView, 
-            "/ while being blocked by some other modalView.
+	modalGroup notNil ifTrue:[
+	    "/ an incoming event for a masterView, 
+	    "/ while being blocked by some other modalView.
 
-            modalTops := modalGroup topViews.
-            modalTops size > 0 ifTrue:[
-                modalTop := modalTops first.
-            ].
+	    modalTops := modalGroup topViews.
+	    modalTops size > 0 ifTrue:[
+		modalTop := modalTops first.
+	    ].
 
-            event isKeyEvent ifTrue:[
-                "/ forward keyboard events to my modal
-                "/ groups first topView ...
-                modalTop notNil ifTrue:[
-                    focus := modalTop.
-                    modalDelegate := true.
-                ]
-            ] ifFalse:[
-                event isFocusEvent ifTrue:[
-                    event isFocusInEvent ifTrue:[
-                        "/ focusIn is forwarded to the modalGroup
-                        "/ (since keyboard is forwarded)
-                        event view:modalTop.
-                        focus := modalTop.
-                    ] ifFalse:[
-                        "/ focusOut goes to both the modal and
-                        "/ the blocked main-group
-                        "/ (actually, only the very first focusOut
-                        "/  is needed in the mainGroup (to turn off the cursor)
-                        "/  all others are only needed in the modalGroup)
+	    event isKeyEvent ifTrue:[
+		"/ forward keyboard events to my modal
+		"/ groups first topView ...
+		modalTop notNil ifTrue:[
+		    focus := modalTop.
+		    modalDelegate := true.
+		]
+	    ] ifFalse:[
+		event isFocusEvent ifTrue:[
+		    event isFocusInEvent ifTrue:[
+			"/ focusIn is forwarded to the modalGroup
+			"/ (since keyboard is forwarded)
+			event view:modalTop.
+			focus := modalTop.
+		    ] ifFalse:[
+			"/ focusOut goes to both the modal and
+			"/ the blocked main-group
+			"/ (actually, only the very first focusOut
+			"/  is needed in the mainGroup (to turn off the cursor)
+			"/  all others are only needed in the modalGroup)
 "/                            syntheticEvent := event copy.
 "/                            syntheticEvent view:modalTop.
 "/                            LastEventQuerySignal handle:[:ex |
@@ -1156,97 +1156,97 @@
 "/                            ] do:[
 "/                                syntheticEvent sendEventWithFocusOn:nil.
 "/                            ].
-                        event view:modalTop.
-                    ].
-                    modalDelegate := true.
-                ] ifFalse:[
-                    event isPointerLeaveEvent ifTrue:[
-                    ] ifFalse:[
-                        event isUserEvent ifTrue:[
-                            ignore := true
-                        ]
-                    ]
-                ]
-            ]
-        ].
+			event view:modalTop.
+		    ].
+		    modalDelegate := true.
+		] ifFalse:[
+		    event isPointerLeaveEvent ifTrue:[
+		    ] ifFalse:[
+			event isUserEvent ifTrue:[
+			    ignore := true
+			]
+		    ]
+		]
+	    ]
+	].
 
-        ignore ifFalse:[
-            (views notNil or:[topViews notNil]) ifTrue:[
-                LastEventQuerySignal handle:[:ex |
-                    ex proceedWith:event
-                ] do:[
-                    (preEventHook  notNil 
-                    and:[preEventHook processEvent:event]) ifTrue:[
-                        ignore := true.
-                    ].
+	ignore ifFalse:[
+	    (views notNil or:[topViews notNil]) ifTrue:[
+		LastEventQuerySignal handle:[:ex |
+		    ex proceedWith:event
+		] do:[
+		    (preEventHook  notNil 
+		    and:[preEventHook processEvent:event]) ifTrue:[
+			ignore := true.
+		    ].
 
-                    ignore ifFalse:[
-                        evView := event view.
+		    ignore ifFalse:[
+			evView := event view.
 
-                        event isKeyPressEvent ifTrue:[
-                            key := event key.
+			event isKeyPressEvent ifTrue:[
+			    key := event key.
 
-                            key == #Escape ifTrue:[
-                                modalDelegate ifTrue:[
-                                    modalTop hideRequest
-                                ] ifFalse:[
-                                    isModal ifTrue:[
-                                        topViews first hideRequest
-                                    ]
-                                ]
-                            ]
-                        ] ifFalse:[
-                            "/
-                            "/ keep track of which view has the pointer
-                            "/
-                            event isPointerEnterEvent ifTrue:[
-                                pointerView := evView
-                            ] ifFalse:[
-                                event isPointerLeaveEvent ifTrue:[
-                                    pointerView := nil
-                                ]
-                            ]
-                        ].
+			    key == #Escape ifTrue:[
+				modalDelegate ifTrue:[
+				    modalTop hideRequest
+				] ifFalse:[
+				    isModal ifTrue:[
+					topViews first hideRequest
+				    ]
+				]
+			    ]
+			] ifFalse:[
+			    "/
+			    "/ keep track of which view has the pointer
+			    "/
+			    event isPointerEnterEvent ifTrue:[
+				pointerView := evView
+			    ] ifFalse:[
+				event isPointerLeaveEvent ifTrue:[
+				    pointerView := nil
+				]
+			    ]
+			].
 
-                        "/
-                        "/  buttonPress events turn off explicit focus, and revert
-                        "/  to implicit focus control
-                        "/
-                        (focusView notNil
-                        and:[event isButtonPressEvent]) ifTrue:[
-                            self focusView:nil
-                        ].
+			"/
+			"/  buttonPress events turn off explicit focus, and revert
+			"/  to implicit focus control
+			"/
+			(focusView notNil
+			and:[event isButtonPressEvent]) ifTrue:[
+			    self focusView:nil
+			].
 
-                        LastActiveGroup := self.
-                        LastActiveProcess := Processor activeProcess.
+			LastActiveGroup := self.
+			LastActiveProcess := Processor activeProcess.
 
-                        "
-                         if there is no view information in the event,
-                         it must have been sent directly to the sensor.
-                         Send it to the first topView.
-                        "
-                        evType := event type.
-                        evArgs := event arguments.
+			"
+			 if there is no view information in the event,
+			 it must have been sent directly to the sensor.
+			 Send it to the first topView.
+			"
+			evType := event type.
+			evArgs := event arguments.
 
-                        evView isNil ifTrue:[
-                            (firstTop := topViews first) notNil ifTrue:[
-                                firstTop perform:evType withArguments:evArgs
-                            ]
-                        ] ifFalse:[
-                            evView
-                                dispatchEvent:evType 
-                                arguments:evArgs 
-                                withFocusOn:focus 
-                                delegate:true
-                        ]
-                    ].
+			evView isNil ifTrue:[
+			    (firstTop := topViews first) notNil ifTrue:[
+				firstTop perform:evType withArguments:evArgs
+			    ]
+			] ifFalse:[
+			    evView
+				dispatchEvent:evType 
+				arguments:evArgs 
+				withFocusOn:focus 
+				delegate:true
+			]
+		    ].
 
-                    postEventHook notNil ifTrue:[
-                        postEventHook processEvent:event
-                    ].
-                ]
-            ]
-        ].
+		    postEventHook notNil ifTrue:[
+			postEventHook processEvent:event
+		    ].
+		]
+	    ]
+	].
     ]
 
     "Created: / 5.3.1997 / 11:33:11 / cg"
@@ -1260,58 +1260,58 @@
 
     (sensor := mySensor) isNil ifTrue:[^ self].
     (sensor damageCount ~~ 0) ifTrue:[
-        thisProcess := Processor activeProcess.
+	thisProcess := Processor activeProcess.
 
-        [(event := sensor nextDamage) notNil] whileTrue:[
-            LastActiveGroup := self.
-            LastActiveProcess := thisProcess.
+	[(event := sensor nextDamage) notNil] whileTrue:[
+	    LastActiveGroup := self.
+	    LastActiveProcess := thisProcess.
 
-            (views notNil or:[topViews notNil]) ifTrue:[
-                LastEventQuerySignal handle:[:ex |
-                    ex proceedWith:event
-                ] do:[
-                    (preEventHook notNil 
-                    and:[preEventHook processEvent:event]) ifFalse:[
-                        view := event view.
+	    (views notNil or:[topViews notNil]) ifTrue:[
+		LastEventQuerySignal handle:[:ex |
+		    ex proceedWith:event
+		] do:[
+		    (preEventHook notNil 
+		    and:[preEventHook processEvent:event]) ifFalse:[
+			view := event view.
 
-                        event isDamage ifTrue:[
-                            "/
-                            "/ if the view is no longer shown (iconified or closed),
-                            "/ this is a leftover event and ignored.
-                            "/
-                            view shown ifTrue:[
-                                LastActiveGroup := self.
-                                LastActiveProcess := thisProcess.
+			event isDamage ifTrue:[
+			    "/
+			    "/ if the view is no longer shown (iconified or closed),
+			    "/ this is a leftover event and ignored.
+			    "/
+			    view shown ifTrue:[
+				LastActiveGroup := self.
+				LastActiveProcess := thisProcess.
 
-                                view
-                                    dispatchEvent:(event type) 
-                                    arguments:(event arguments) 
-                                    withFocusOn:nil 
-                                    delegate:true
+				view
+				    dispatchEvent:(event type) 
+				    arguments:(event arguments) 
+				    withFocusOn:nil 
+				    delegate:true
 
 "/                            ] ifFalse:[
 "/                                ('WGROUP: damage for ' , view displayString , ' ignored') infoPrintCR.
-                            ]
-                        ] ifFalse:[
-                            "
-                             mhmh - could we possibly arrive here ?
-                            "
-                            LastActiveGroup := self.
-                            LastActiveProcess := thisProcess.
-                            "/ event sendEventWithFocusOn:nil.
-                            view
-                                dispatchEvent:(event type) 
-                                arguments:(event arguments) 
-                                withFocusOn:nil 
-                                delegate:true
-                        ]
-                    ].
-                    postEventHook notNil ifTrue:[
-                        postEventHook processEvent:event
-                    ]
-                ]
-            ]
-        ]
+			    ]
+			] ifFalse:[
+			    "
+			     mhmh - could we possibly arrive here ?
+			    "
+			    LastActiveGroup := self.
+			    LastActiveProcess := thisProcess.
+			    "/ event sendEventWithFocusOn:nil.
+			    view
+				dispatchEvent:(event type) 
+				arguments:(event arguments) 
+				withFocusOn:nil 
+				delegate:true
+			]
+		    ].
+		    postEventHook notNil ifTrue:[
+			postEventHook processEvent:event
+		    ]
+		]
+	    ]
+	]
     ]
 
     "Modified: / 17.6.1998 / 09:09:48 / cg"
@@ -1340,44 +1340,44 @@
     thisProcess := Processor activeProcess.
 
     [true] whileTrue:[
-        LastActiveGroup := self.
-        LastActiveProcess := thisProcess.
+	LastActiveGroup := self.
+	LastActiveProcess := thisProcess.
 
-        "/ event := aView nextDamage.
-        event := sensor nextExposeEventFor:someViewOrNil.
-        event isNil ifTrue:[^ self].
+	"/ event := aView nextDamage.
+	event := sensor nextExposeEventFor:someViewOrNil.
+	event isNil ifTrue:[^ self].
 
-        (views notNil or:[topViews notNil]) ifTrue:[
-            LastEventQuerySignal handle:[:ex |
-                ex proceedWith:event
-            ] do:[
-                (preEventHook notNil 
-                and:[preEventHook processEvent:event]) ifFalse:[
-                    view := event view.
-                    "/
-                    "/ if the view is no longer shown (iconified or closed),
-                    "/ this is a leftover event and ignored.
-                    "/
-                    view shown ifTrue:[
-                        rect := event rectangle.
-                        x := rect left.
-                        y := rect top.
-                        w := rect width.
-                        h := rect height.
-                        LastActiveGroup := self.
-                        LastActiveProcess := thisProcess.
-                        view transformation notNil ifTrue:[
-                            view deviceExposeX:x y:y width:w height:h
-                        ] ifFalse:[
-                            view exposeX:x y:y width:w height:h
-                        ]
-                    ]
-                ].
-                postEventHook notNil ifTrue:[
-                    postEventHook processEvent:event
-                ]
-            ]
-        ]
+	(views notNil or:[topViews notNil]) ifTrue:[
+	    LastEventQuerySignal handle:[:ex |
+		ex proceedWith:event
+	    ] do:[
+		(preEventHook notNil 
+		and:[preEventHook processEvent:event]) ifFalse:[
+		    view := event view.
+		    "/
+		    "/ if the view is no longer shown (iconified or closed),
+		    "/ this is a leftover event and ignored.
+		    "/
+		    view shown ifTrue:[
+			rect := event rectangle.
+			x := rect left.
+			y := rect top.
+			w := rect width.
+			h := rect height.
+			LastActiveGroup := self.
+			LastActiveProcess := thisProcess.
+			view transformation notNil ifTrue:[
+			    view deviceExposeX:x y:y width:w height:h
+			] ifFalse:[
+			    view exposeX:x y:y width:w height:h
+			]
+		    ]
+		].
+		postEventHook notNil ifTrue:[
+		    postEventHook processEvent:event
+		]
+	    ]
+	]
     ]
 
     "Created: / 2.7.1997 / 14:32:19 / cg"
@@ -1519,6 +1519,10 @@
 
     "/ a fix focusSequence ...    
     focusSequence notNil ifTrue:[^ focusSequence].
+    topViews isNil ifTrue:[
+	"/ mhmh - a topView-less windowGroup ...
+	^ nil.
+    ].
 
     topViews do:[:top |
 	sequence := top focusSequence.
@@ -1543,14 +1547,21 @@
 focusToView:aViewOrNil
     "give focus to aViewOrNil - if its in my focusSequence"
 
-    |seq|
+    |seq doAssignFocusView|
 
     focusView == aViewOrNil ifFalse:[
-        (seq := self focusSequence) notNil ifTrue:[
-            (seq includes:aViewOrNil) ifTrue:[
-                self focusView:aViewOrNil.
-            ]
-        ]
+	doAssignFocusView := false.
+	topViews isNil ifTrue:[
+	    "/ mhmh - a topview-less windowGroup
+	    doAssignFocusView := true.
+	] ifFalse:[
+	    (seq := self focusSequence) notNil ifTrue:[
+		doAssignFocusView := (seq includes:aViewOrNil).
+	    ]
+	].
+	doAssignFocusView ifTrue:[
+	    self focusView:aViewOrNil.
+	]
     ]
 
     "Created: / 18.9.1998 / 16:28:27 / cg"
@@ -1656,17 +1667,17 @@
     "restore the original cursors in all of my views"
 
     self allViewsDo:[:aView |  
-        |c dev id cid|
+	|c dev id cid|
 
-        dev := aView graphicsDevice.
-        dev notNil ifTrue:[
-            (id := aView id) notNil ifTrue:[
-                c := aView cursor onDevice:dev.
-                (cid := c id) notNil ifTrue:[
-                    dev setCursor:cid in:id.
-                ]
-            ]
-        ]
+	dev := aView graphicsDevice.
+	dev notNil ifTrue:[
+	    (id := aView id) notNil ifTrue:[
+		c := aView cursor onDevice:dev.
+		(cid := c id) notNil ifTrue:[
+		    dev setCursor:cid in:id.
+		]
+	    ]
+	]
     ].
 
     "Modified: / 22.4.1998 / 14:28:22 / cg"
@@ -1693,15 +1704,15 @@
 
     c := aCursor.
     self allViewsDo:[:aView |  
-        dev := aView graphicsDevice.
-        dev notNil ifTrue:[
-            c := c onDevice:dev.
-            (cId := c id) notNil ifTrue:[
-               (vId := aView id) notNil ifTrue:[
-                    dev setCursor:cId in:vId.
-                ]
-            ]
-        ]
+	dev := aView graphicsDevice.
+	dev notNil ifTrue:[
+	    c := c onDevice:dev.
+	    (cId := c id) notNil ifTrue:[
+	       (vId := aView id) notNil ifTrue:[
+		    dev setCursor:cId in:vId.
+		]
+	    ]
+	]
     ].
 
     "Modified: / 22.4.1998 / 14:26:45 / cg"
@@ -1716,7 +1727,7 @@
 
     dev := self graphicsDevice.   
     dev isNil ifTrue:[
-        ^ aBlock value
+	^ aBlock value
     ].
 
     deviceCursor := aCursor onDevice:dev.
@@ -1726,39 +1737,39 @@
     "
     oldCursors := IdentityDictionary new.
     self allViewsDo:[:aView |
-        |old|
+	|old|
 
-        old := aView cursor.
-        old ~~ aCursor ifTrue:[
-            oldCursors at:aView put:old.
-            aView cursor:deviceCursor now:false
-        ]
+	old := aView cursor.
+	old ~~ aCursor ifTrue:[
+	    oldCursors at:aView put:old.
+	    aView cursor:deviceCursor now:false
+	]
     ].
 
     oldCursors size == 0 ifTrue:[
-        action := aBlock
+	action := aBlock
     ] ifFalse:[
-        action := [
-                    |rslt|
+	action := [
+		    |rslt|
 
-                    "/
-                    "/ here sync looks better; flush leads to almost invisible cursors when accepting.
-                    "/ I dont really know why (maybe unix does not context-switch to the Xserver
-                    "/ early enough after the requests have been sent ?)
-                    "/
-                    dev sync.
+		    "/
+		    "/ here sync looks better; flush leads to almost invisible cursors when accepting.
+		    "/ I dont really know why (maybe unix does not context-switch to the Xserver
+		    "/ early enough after the requests have been sent ?)
+		    "/
+		    dev sync.
 
-                    rslt := aBlock valueNowOrOnUnwindDo:[
-                        "
-                         restore cursors from the mapping
-                        "
-                        oldCursors keysAndValuesDo:[:view :cursor |
-                            view cursor:cursor now:false.
-                        ].
-                        dev flush
-                    ].
-                    rslt
-                  ]
+		    rslt := aBlock valueNowOrOnUnwindDo:[
+			"
+			 restore cursors from the mapping
+			"
+			oldCursors keysAndValuesDo:[:view :cursor |
+			    view cursor:cursor now:false.
+			].
+			dev flush
+		    ].
+		    rslt
+		  ]
     ].
 
 "/    (self isModal and:[previousGroup notNil]) ifTrue:[
@@ -1841,6 +1852,6 @@
 !WindowGroup class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/Attic/WGroup.st,v 1.144 1998-09-18 15:12:34 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/Attic/WGroup.st,v 1.145 1998-09-24 10:02:31 cg Exp $'
 ! !
 WindowGroup initialize!
--- a/WindowGroup.st	Thu Sep 24 12:01:42 1998 +0200
+++ b/WindowGroup.st	Thu Sep 24 12:02:31 1998 +0200
@@ -263,31 +263,31 @@
     activeProcess := Processor activeProcess.
     " caching the last value ..."
     activeProcess == LastActiveProcess ifTrue:[
-        LastActiveGroup process == LastActiveProcess ifTrue:[
-            ^ LastActiveGroup
-        ]
+	LastActiveGroup process == LastActiveProcess ifTrue:[
+	    ^ LastActiveGroup
+	]
     ].
 
     wg := WindowGroupQuerySignal raise.
 
     wg isNil ifTrue:[
-        "/ mhmh - noone willing to answer that question ...
-        "/ (how can this happen ?)
-        groups := self scheduledWindowGroups 
-                    select:[:wg | wg process == activeProcess].
-        groups size == 1 ifTrue:[
-            wg := groups anElement
-        ] ifFalse:[
-            wg := groups detect:[:wg | wg isModal] ifNone:nil.
-            wg isNil ifTrue:[
-                wg := groups anElement
-            ]
-        ].
+	"/ mhmh - noone willing to answer that question ...
+	"/ (how can this happen ?)
+	groups := self scheduledWindowGroups 
+		    select:[:wg | wg process == activeProcess].
+	groups size == 1 ifTrue:[
+	    wg := groups anElement
+	] ifFalse:[
+	    wg := groups detect:[:wg | wg isModal] ifNone:nil.
+	    wg isNil ifTrue:[
+		wg := groups anElement
+	    ]
+	].
     ].
 
     wg notNil ifTrue:[
-        LastActiveProcess := activeProcess.
-        LastActiveGroup := wg.
+	LastActiveProcess := activeProcess.
+	LastActiveGroup := wg.
     ].
     ^ wg
 
@@ -356,34 +356,34 @@
     |dev|
 
     topViews notNil ifTrue:[
-        topViews do:[:v |
-            |app|
+	topViews do:[:v |
+	    |app|
 
-            (app := v application) notNil ifTrue:[
-                "/
-                "/ ok, it has an application;
-                "/ ask it for preferences.
-                "/
-                (dev := app graphicsDevice) notNil ifTrue:[
-                    ^ dev
-                ]
-            ].
-            (dev := v graphicsDevice) notNil ifTrue:[
-                ^ dev
-            ]
-        ]
+	    (app := v application) notNil ifTrue:[
+		"/
+		"/ ok, it has an application;
+		"/ ask it for preferences.
+		"/
+		(dev := app graphicsDevice) notNil ifTrue:[
+		    ^ dev
+		]
+	    ].
+	    (dev := v graphicsDevice) notNil ifTrue:[
+		^ dev
+	    ]
+	]
     ].
     views notNil ifTrue:[
-        views do:[:v |
-            (dev := v graphicsDevice) notNil ifTrue:[
-                ^ dev
-            ]
-        ]
+	views do:[:v |
+	    (dev := v graphicsDevice) notNil ifTrue:[
+		^ dev
+	    ]
+	]
     ].
     "/ ask the previousGroup; I could be a popUp-views group,
     "/ which has already closed its views (and is performing its action)
     previousGroup notNil ifTrue:[
-        ^ previousGroup graphicsDevice
+	^ previousGroup graphicsDevice
     ].
     ^ nil
 
@@ -454,9 +454,9 @@
     "return the windowGroups process"
 
     myProcess isNil ifTrue:[
-        previousGroup notNil ifTrue:[
-            ^ previousGroup process
-        ]
+	previousGroup notNil ifTrue:[
+	    ^ previousGroup process
+	]
     ].
     ^ myProcess
 
@@ -918,168 +918,168 @@
      and aBlock evaluates to true.
 
      Some signals are caught & handled: 
-        LeaveSignal forces an exit from the eventLoop;
-        AbortSignal brings us back into the loop, processing the next event;
-        ActivityNotifications send a #showActivity: if nonModal, 
-        otherwise they are ignored."
+	LeaveSignal forces an exit from the eventLoop;
+	AbortSignal brings us back into the loop, processing the next event;
+	ActivityNotifications send a #showActivity: if nonModal, 
+	otherwise they are ignored."
 
     |thisProcess sigs mainSema prevSema|
 
     thisProcess := Processor activeProcess.
 
     sigs := SignalSet 
-                with:AbortSignal 
-                with:LeaveSignal 
-                with:(self class activityNotificationSignal).
+		with:AbortSignal 
+		with:LeaveSignal 
+		with:(self class activityNotificationSignal).
 
     [
-        |p g s mainGroup mySema waitSema groupForSema|
+	|p g s mainGroup mySema waitSema groupForSema|
 
-        waitSema := mySema := mySensor eventSemaphore.
+	waitSema := mySema := mySensor eventSemaphore.
 
-        isModal ifTrue:[
-            mainGroup := self mainGroup.
-            mainGroup == self ifTrue:[
-                mainGroup := nil
-            ].
-        ] ifFalse:[
-            mainGroup := previousGroup
-        ].
+	isModal ifTrue:[
+	    mainGroup := self mainGroup.
+	    mainGroup == self ifTrue:[
+		mainGroup := nil
+	    ].
+	] ifFalse:[
+	    mainGroup := previousGroup
+	].
         
-        mainGroup notNil ifTrue:[
-            mainSema := mainGroup sensor eventSemaphore.
-            waitSema := SemaphoreSet with:mySema with:mainSema.
+	mainGroup notNil ifTrue:[
+	    mainSema := mainGroup sensor eventSemaphore.
+	    waitSema := SemaphoreSet with:mySema with:mainSema.
 
-            "/ must also care for all other groups in between
-            "/ (in case its a modal dialog opened from a modal dialog)
+	    "/ must also care for all other groups in between
+	    "/ (in case its a modal dialog opened from a modal dialog)
         
-            g := previousGroup.
-            g ~~ mainGroup ifTrue:[
-                groupForSema := IdentityDictionary new.
-                [g ~~ mainGroup] whileTrue:[
-                    s := g sensor eventSemaphore.
-                    waitSema add:s.
-                    groupForSema at:s put:g.
-                    g := g previousGroup.
-                ]
-            ].
-        ].
+	    g := previousGroup.
+	    g ~~ mainGroup ifTrue:[
+		groupForSema := IdentityDictionary new.
+		[g ~~ mainGroup] whileTrue:[
+		    s := g sensor eventSemaphore.
+		    waitSema add:s.
+		    groupForSema at:s put:g.
+		    g := g previousGroup.
+		]
+	    ].
+	].
 
-        [aBlock value] whileTrue:[ 
-            LastActiveGroup := self.
-            LastActiveProcess := thisProcess.
+	[aBlock value] whileTrue:[ 
+	    LastActiveGroup := self.
+	    LastActiveProcess := thisProcess.
 
-            (views isNil and:[topViews isNil]) ifTrue:[
-                myProcess notNil ifTrue:[
-                    p := myProcess.
-                    myProcess := nil.
-                    p terminate.
-                    "not reached - there is no life after death"
-                ].
-                "
-                 this is the end of a modal loop
-                 (not having a private process ...)
-                "
-                ^ self
-            ].
+	    (views isNil and:[topViews isNil]) ifTrue:[
+		myProcess notNil ifTrue:[
+		    p := myProcess.
+		    myProcess := nil.
+		    p terminate.
+		    "not reached - there is no life after death"
+		].
+		"
+		 this is the end of a modal loop
+		 (not having a private process ...)
+		"
+		^ self
+	    ].
 
-            sigs handle:[:ex |
-                |theSig|
+	    sigs handle:[:ex |
+		|theSig|
 
-                (theSig := ex signal) == AbortSignal ifTrue:[
-                    "/
-                    "/ on abort, stay in loop
-                    "/
-                    ex return
-                ].
-                theSig == LeaveSignal ifTrue:[
-                    "/
-                    "/ on leave, exit the event loop
-                    "/
-                    ^ self
-                ].
+		(theSig := ex signal) == AbortSignal ifTrue:[
+		    "/
+		    "/ on abort, stay in loop
+		    "/
+		    ex return
+		].
+		theSig == LeaveSignal ifTrue:[
+		    "/
+		    "/ on leave, exit the event loop
+		    "/
+		    ^ self
+		].
 
-                "/ ActivityNotification
-                "/
-                "/ if I am a modal-group, let it be handled
-                "/ by the outer main-groups handler
-                "/ otherwise show the activityMessage and continue.
-                "/
-                isModal ifTrue:[
-                    ex reject
-                    "never reached"
-                ].
-                self showActivity:(ex errorString).
-                ex proceed.
-            ] do:[
-                |dev gotSema mainView|
+		"/ ActivityNotification
+		"/
+		"/ if I am a modal-group, let it be handled
+		"/ by the outer main-groups handler
+		"/ otherwise show the activityMessage and continue.
+		"/
+		isModal ifTrue:[
+		    ex reject
+		    "never reached"
+		].
+		self showActivity:(ex errorString).
+		ex proceed.
+	    ] do:[
+		|dev gotSema mainView|
 
-                "/ Flush device output before going to sleep. 
-                "/ This may produce more events to arrive.
-                "/ Q: is this still needed (see suspendAction) ?
+		"/ Flush device output before going to sleep. 
+		"/ This may produce more events to arrive.
+		"/ Q: is this still needed (see suspendAction) ?
 
 "/                dev := self graphicsDevice.
 "/                dev notNil ifTrue:[dev flush].
 
-                "/ now, wait for an event to arrive
-                thisProcess setStateTo:#eventWait if:#active.
-                waitSema isNil ifTrue:[
-                    "/ oops - how can this happen ....
-                    ^ self.
-                ].
-                gotSema := waitSema wait.
-                LastActiveGroup := self.
-                LastActiveProcess := thisProcess.
+		"/ now, wait for an event to arrive
+		thisProcess setStateTo:#eventWait if:#active.
+		waitSema isNil ifTrue:[
+		    "/ oops - how can this happen ....
+		    ^ self.
+		].
+		gotSema := waitSema wait.
+		LastActiveGroup := self.
+		LastActiveProcess := thisProcess.
 
-                "/ some bad guy ;-) could have closed all down
-                "/ in the meanwhile ...
+		"/ some bad guy ;-) could have closed all down
+		"/ in the meanwhile ...
 
-                mySensor notNil ifTrue:[
-                    gotSema == mySema ifTrue:[
-                        "/
-                        "/ an event for me 
-                        "/
-                        self processEventsWithModalGroup:nil
-                    ] ifFalse:[
-                        groupForSema notNil ifTrue:[
-                            g := groupForSema at:gotSema ifAbsent:nil.
-                            g := g ? mainGroup.
-                        ] ifFalse:[
-                            g := mainGroup
-                        ].
+		mySensor notNil ifTrue:[
+		    gotSema == mySema ifTrue:[
+			"/
+			"/ an event for me 
+			"/
+			self processEventsWithModalGroup:nil
+		    ] ifFalse:[
+			groupForSema notNil ifTrue:[
+			    g := groupForSema at:gotSema ifAbsent:nil.
+			    g := g ? mainGroup.
+			] ifFalse:[
+			    g := mainGroup
+			].
 
-                        "/
-                        "/ an event for my mainGroup 
-                        "/
-                        g topViews notNil ifTrue:[
-                            mainView := g topViews first
-                        ].
-                        mainView notNil ifTrue:[
-                            "/
-                            "/ if anything happened to the mainGroup
-                            "/ bring my own topView back to the front
-                            "/ This keeps modalBoxes visible
-                            "/
-                            (g sensor hasConfigureEventFor:mainView) ifTrue:[
-                                topViews size > 0 ifTrue:[
-                                    topViews first raiseDeiconified
-                                ]
-                            ]
-                        ].
-                        "
-                         if modal, also check for redraw events in my maingroup
-                         (we arrive here after we woke up on maingroup sensor eventSemaphore)
-                        "
-                        g processEventsWithModalGroup:self.
-                    ]
-                ]
-            ].
-        ].
+			"/
+			"/ an event for my mainGroup 
+			"/
+			g topViews notNil ifTrue:[
+			    mainView := g topViews first
+			].
+			mainView notNil ifTrue:[
+			    "/
+			    "/ if anything happened to the mainGroup
+			    "/ bring my own topView back to the front
+			    "/ This keeps modalBoxes visible
+			    "/
+			    (g sensor hasConfigureEventFor:mainView) ifTrue:[
+				topViews size > 0 ifTrue:[
+				    topViews first raiseDeiconified
+				]
+			    ]
+			].
+			"
+			 if modal, also check for redraw events in my maingroup
+			 (we arrive here after we woke up on maingroup sensor eventSemaphore)
+			"
+			g processEventsWithModalGroup:self.
+		    ]
+		]
+	    ].
+	].
     ] valueNowOrOnUnwindDo:[
-        "/
-        "/ perform any cleanupActions
-        "/
-        cleanupActions notNil ifTrue:[cleanupActions value]
+	"/
+	"/ perform any cleanupActions
+	"/
+	cleanupActions notNil ifTrue:[cleanupActions value]
     ]
 
     "Modified: / 14.12.1995 / 11:12:24 / stefan"
@@ -1116,39 +1116,39 @@
 
     [mySensor notNil
      and:[(event := mySensor nextEvent) notNil]] whileTrue:[
-        ignore := false.
-        focus := focusView.
-        modalDelegate := false.
+	ignore := false.
+	focus := focusView.
+	modalDelegate := false.
 
-        modalGroup notNil ifTrue:[
-            "/ an incoming event for a masterView, 
-            "/ while being blocked by some other modalView.
+	modalGroup notNil ifTrue:[
+	    "/ an incoming event for a masterView, 
+	    "/ while being blocked by some other modalView.
 
-            modalTops := modalGroup topViews.
-            modalTops size > 0 ifTrue:[
-                modalTop := modalTops first.
-            ].
+	    modalTops := modalGroup topViews.
+	    modalTops size > 0 ifTrue:[
+		modalTop := modalTops first.
+	    ].
 
-            event isKeyEvent ifTrue:[
-                "/ forward keyboard events to my modal
-                "/ groups first topView ...
-                modalTop notNil ifTrue:[
-                    focus := modalTop.
-                    modalDelegate := true.
-                ]
-            ] ifFalse:[
-                event isFocusEvent ifTrue:[
-                    event isFocusInEvent ifTrue:[
-                        "/ focusIn is forwarded to the modalGroup
-                        "/ (since keyboard is forwarded)
-                        event view:modalTop.
-                        focus := modalTop.
-                    ] ifFalse:[
-                        "/ focusOut goes to both the modal and
-                        "/ the blocked main-group
-                        "/ (actually, only the very first focusOut
-                        "/  is needed in the mainGroup (to turn off the cursor)
-                        "/  all others are only needed in the modalGroup)
+	    event isKeyEvent ifTrue:[
+		"/ forward keyboard events to my modal
+		"/ groups first topView ...
+		modalTop notNil ifTrue:[
+		    focus := modalTop.
+		    modalDelegate := true.
+		]
+	    ] ifFalse:[
+		event isFocusEvent ifTrue:[
+		    event isFocusInEvent ifTrue:[
+			"/ focusIn is forwarded to the modalGroup
+			"/ (since keyboard is forwarded)
+			event view:modalTop.
+			focus := modalTop.
+		    ] ifFalse:[
+			"/ focusOut goes to both the modal and
+			"/ the blocked main-group
+			"/ (actually, only the very first focusOut
+			"/  is needed in the mainGroup (to turn off the cursor)
+			"/  all others are only needed in the modalGroup)
 "/                            syntheticEvent := event copy.
 "/                            syntheticEvent view:modalTop.
 "/                            LastEventQuerySignal handle:[:ex |
@@ -1156,97 +1156,97 @@
 "/                            ] do:[
 "/                                syntheticEvent sendEventWithFocusOn:nil.
 "/                            ].
-                        event view:modalTop.
-                    ].
-                    modalDelegate := true.
-                ] ifFalse:[
-                    event isPointerLeaveEvent ifTrue:[
-                    ] ifFalse:[
-                        event isUserEvent ifTrue:[
-                            ignore := true
-                        ]
-                    ]
-                ]
-            ]
-        ].
+			event view:modalTop.
+		    ].
+		    modalDelegate := true.
+		] ifFalse:[
+		    event isPointerLeaveEvent ifTrue:[
+		    ] ifFalse:[
+			event isUserEvent ifTrue:[
+			    ignore := true
+			]
+		    ]
+		]
+	    ]
+	].
 
-        ignore ifFalse:[
-            (views notNil or:[topViews notNil]) ifTrue:[
-                LastEventQuerySignal handle:[:ex |
-                    ex proceedWith:event
-                ] do:[
-                    (preEventHook  notNil 
-                    and:[preEventHook processEvent:event]) ifTrue:[
-                        ignore := true.
-                    ].
+	ignore ifFalse:[
+	    (views notNil or:[topViews notNil]) ifTrue:[
+		LastEventQuerySignal handle:[:ex |
+		    ex proceedWith:event
+		] do:[
+		    (preEventHook  notNil 
+		    and:[preEventHook processEvent:event]) ifTrue:[
+			ignore := true.
+		    ].
 
-                    ignore ifFalse:[
-                        evView := event view.
+		    ignore ifFalse:[
+			evView := event view.
 
-                        event isKeyPressEvent ifTrue:[
-                            key := event key.
+			event isKeyPressEvent ifTrue:[
+			    key := event key.
 
-                            key == #Escape ifTrue:[
-                                modalDelegate ifTrue:[
-                                    modalTop hideRequest
-                                ] ifFalse:[
-                                    isModal ifTrue:[
-                                        topViews first hideRequest
-                                    ]
-                                ]
-                            ]
-                        ] ifFalse:[
-                            "/
-                            "/ keep track of which view has the pointer
-                            "/
-                            event isPointerEnterEvent ifTrue:[
-                                pointerView := evView
-                            ] ifFalse:[
-                                event isPointerLeaveEvent ifTrue:[
-                                    pointerView := nil
-                                ]
-                            ]
-                        ].
+			    key == #Escape ifTrue:[
+				modalDelegate ifTrue:[
+				    modalTop hideRequest
+				] ifFalse:[
+				    isModal ifTrue:[
+					topViews first hideRequest
+				    ]
+				]
+			    ]
+			] ifFalse:[
+			    "/
+			    "/ keep track of which view has the pointer
+			    "/
+			    event isPointerEnterEvent ifTrue:[
+				pointerView := evView
+			    ] ifFalse:[
+				event isPointerLeaveEvent ifTrue:[
+				    pointerView := nil
+				]
+			    ]
+			].
 
-                        "/
-                        "/  buttonPress events turn off explicit focus, and revert
-                        "/  to implicit focus control
-                        "/
-                        (focusView notNil
-                        and:[event isButtonPressEvent]) ifTrue:[
-                            self focusView:nil
-                        ].
+			"/
+			"/  buttonPress events turn off explicit focus, and revert
+			"/  to implicit focus control
+			"/
+			(focusView notNil
+			and:[event isButtonPressEvent]) ifTrue:[
+			    self focusView:nil
+			].
 
-                        LastActiveGroup := self.
-                        LastActiveProcess := Processor activeProcess.
+			LastActiveGroup := self.
+			LastActiveProcess := Processor activeProcess.
 
-                        "
-                         if there is no view information in the event,
-                         it must have been sent directly to the sensor.
-                         Send it to the first topView.
-                        "
-                        evType := event type.
-                        evArgs := event arguments.
+			"
+			 if there is no view information in the event,
+			 it must have been sent directly to the sensor.
+			 Send it to the first topView.
+			"
+			evType := event type.
+			evArgs := event arguments.
 
-                        evView isNil ifTrue:[
-                            (firstTop := topViews first) notNil ifTrue:[
-                                firstTop perform:evType withArguments:evArgs
-                            ]
-                        ] ifFalse:[
-                            evView
-                                dispatchEvent:evType 
-                                arguments:evArgs 
-                                withFocusOn:focus 
-                                delegate:true
-                        ]
-                    ].
+			evView isNil ifTrue:[
+			    (firstTop := topViews first) notNil ifTrue:[
+				firstTop perform:evType withArguments:evArgs
+			    ]
+			] ifFalse:[
+			    evView
+				dispatchEvent:evType 
+				arguments:evArgs 
+				withFocusOn:focus 
+				delegate:true
+			]
+		    ].
 
-                    postEventHook notNil ifTrue:[
-                        postEventHook processEvent:event
-                    ].
-                ]
-            ]
-        ].
+		    postEventHook notNil ifTrue:[
+			postEventHook processEvent:event
+		    ].
+		]
+	    ]
+	].
     ]
 
     "Created: / 5.3.1997 / 11:33:11 / cg"
@@ -1260,58 +1260,58 @@
 
     (sensor := mySensor) isNil ifTrue:[^ self].
     (sensor damageCount ~~ 0) ifTrue:[
-        thisProcess := Processor activeProcess.
+	thisProcess := Processor activeProcess.
 
-        [(event := sensor nextDamage) notNil] whileTrue:[
-            LastActiveGroup := self.
-            LastActiveProcess := thisProcess.
+	[(event := sensor nextDamage) notNil] whileTrue:[
+	    LastActiveGroup := self.
+	    LastActiveProcess := thisProcess.
 
-            (views notNil or:[topViews notNil]) ifTrue:[
-                LastEventQuerySignal handle:[:ex |
-                    ex proceedWith:event
-                ] do:[
-                    (preEventHook notNil 
-                    and:[preEventHook processEvent:event]) ifFalse:[
-                        view := event view.
+	    (views notNil or:[topViews notNil]) ifTrue:[
+		LastEventQuerySignal handle:[:ex |
+		    ex proceedWith:event
+		] do:[
+		    (preEventHook notNil 
+		    and:[preEventHook processEvent:event]) ifFalse:[
+			view := event view.
 
-                        event isDamage ifTrue:[
-                            "/
-                            "/ if the view is no longer shown (iconified or closed),
-                            "/ this is a leftover event and ignored.
-                            "/
-                            view shown ifTrue:[
-                                LastActiveGroup := self.
-                                LastActiveProcess := thisProcess.
+			event isDamage ifTrue:[
+			    "/
+			    "/ if the view is no longer shown (iconified or closed),
+			    "/ this is a leftover event and ignored.
+			    "/
+			    view shown ifTrue:[
+				LastActiveGroup := self.
+				LastActiveProcess := thisProcess.
 
-                                view
-                                    dispatchEvent:(event type) 
-                                    arguments:(event arguments) 
-                                    withFocusOn:nil 
-                                    delegate:true
+				view
+				    dispatchEvent:(event type) 
+				    arguments:(event arguments) 
+				    withFocusOn:nil 
+				    delegate:true
 
 "/                            ] ifFalse:[
 "/                                ('WGROUP: damage for ' , view displayString , ' ignored') infoPrintCR.
-                            ]
-                        ] ifFalse:[
-                            "
-                             mhmh - could we possibly arrive here ?
-                            "
-                            LastActiveGroup := self.
-                            LastActiveProcess := thisProcess.
-                            "/ event sendEventWithFocusOn:nil.
-                            view
-                                dispatchEvent:(event type) 
-                                arguments:(event arguments) 
-                                withFocusOn:nil 
-                                delegate:true
-                        ]
-                    ].
-                    postEventHook notNil ifTrue:[
-                        postEventHook processEvent:event
-                    ]
-                ]
-            ]
-        ]
+			    ]
+			] ifFalse:[
+			    "
+			     mhmh - could we possibly arrive here ?
+			    "
+			    LastActiveGroup := self.
+			    LastActiveProcess := thisProcess.
+			    "/ event sendEventWithFocusOn:nil.
+			    view
+				dispatchEvent:(event type) 
+				arguments:(event arguments) 
+				withFocusOn:nil 
+				delegate:true
+			]
+		    ].
+		    postEventHook notNil ifTrue:[
+			postEventHook processEvent:event
+		    ]
+		]
+	    ]
+	]
     ]
 
     "Modified: / 17.6.1998 / 09:09:48 / cg"
@@ -1340,44 +1340,44 @@
     thisProcess := Processor activeProcess.
 
     [true] whileTrue:[
-        LastActiveGroup := self.
-        LastActiveProcess := thisProcess.
+	LastActiveGroup := self.
+	LastActiveProcess := thisProcess.
 
-        "/ event := aView nextDamage.
-        event := sensor nextExposeEventFor:someViewOrNil.
-        event isNil ifTrue:[^ self].
+	"/ event := aView nextDamage.
+	event := sensor nextExposeEventFor:someViewOrNil.
+	event isNil ifTrue:[^ self].
 
-        (views notNil or:[topViews notNil]) ifTrue:[
-            LastEventQuerySignal handle:[:ex |
-                ex proceedWith:event
-            ] do:[
-                (preEventHook notNil 
-                and:[preEventHook processEvent:event]) ifFalse:[
-                    view := event view.
-                    "/
-                    "/ if the view is no longer shown (iconified or closed),
-                    "/ this is a leftover event and ignored.
-                    "/
-                    view shown ifTrue:[
-                        rect := event rectangle.
-                        x := rect left.
-                        y := rect top.
-                        w := rect width.
-                        h := rect height.
-                        LastActiveGroup := self.
-                        LastActiveProcess := thisProcess.
-                        view transformation notNil ifTrue:[
-                            view deviceExposeX:x y:y width:w height:h
-                        ] ifFalse:[
-                            view exposeX:x y:y width:w height:h
-                        ]
-                    ]
-                ].
-                postEventHook notNil ifTrue:[
-                    postEventHook processEvent:event
-                ]
-            ]
-        ]
+	(views notNil or:[topViews notNil]) ifTrue:[
+	    LastEventQuerySignal handle:[:ex |
+		ex proceedWith:event
+	    ] do:[
+		(preEventHook notNil 
+		and:[preEventHook processEvent:event]) ifFalse:[
+		    view := event view.
+		    "/
+		    "/ if the view is no longer shown (iconified or closed),
+		    "/ this is a leftover event and ignored.
+		    "/
+		    view shown ifTrue:[
+			rect := event rectangle.
+			x := rect left.
+			y := rect top.
+			w := rect width.
+			h := rect height.
+			LastActiveGroup := self.
+			LastActiveProcess := thisProcess.
+			view transformation notNil ifTrue:[
+			    view deviceExposeX:x y:y width:w height:h
+			] ifFalse:[
+			    view exposeX:x y:y width:w height:h
+			]
+		    ]
+		].
+		postEventHook notNil ifTrue:[
+		    postEventHook processEvent:event
+		]
+	    ]
+	]
     ]
 
     "Created: / 2.7.1997 / 14:32:19 / cg"
@@ -1519,6 +1519,10 @@
 
     "/ a fix focusSequence ...    
     focusSequence notNil ifTrue:[^ focusSequence].
+    topViews isNil ifTrue:[
+	"/ mhmh - a topView-less windowGroup ...
+	^ nil.
+    ].
 
     topViews do:[:top |
 	sequence := top focusSequence.
@@ -1543,14 +1547,21 @@
 focusToView:aViewOrNil
     "give focus to aViewOrNil - if its in my focusSequence"
 
-    |seq|
+    |seq doAssignFocusView|
 
     focusView == aViewOrNil ifFalse:[
-        (seq := self focusSequence) notNil ifTrue:[
-            (seq includes:aViewOrNil) ifTrue:[
-                self focusView:aViewOrNil.
-            ]
-        ]
+	doAssignFocusView := false.
+	topViews isNil ifTrue:[
+	    "/ mhmh - a topview-less windowGroup
+	    doAssignFocusView := true.
+	] ifFalse:[
+	    (seq := self focusSequence) notNil ifTrue:[
+		doAssignFocusView := (seq includes:aViewOrNil).
+	    ]
+	].
+	doAssignFocusView ifTrue:[
+	    self focusView:aViewOrNil.
+	]
     ]
 
     "Created: / 18.9.1998 / 16:28:27 / cg"
@@ -1656,17 +1667,17 @@
     "restore the original cursors in all of my views"
 
     self allViewsDo:[:aView |  
-        |c dev id cid|
+	|c dev id cid|
 
-        dev := aView graphicsDevice.
-        dev notNil ifTrue:[
-            (id := aView id) notNil ifTrue:[
-                c := aView cursor onDevice:dev.
-                (cid := c id) notNil ifTrue:[
-                    dev setCursor:cid in:id.
-                ]
-            ]
-        ]
+	dev := aView graphicsDevice.
+	dev notNil ifTrue:[
+	    (id := aView id) notNil ifTrue:[
+		c := aView cursor onDevice:dev.
+		(cid := c id) notNil ifTrue:[
+		    dev setCursor:cid in:id.
+		]
+	    ]
+	]
     ].
 
     "Modified: / 22.4.1998 / 14:28:22 / cg"
@@ -1693,15 +1704,15 @@
 
     c := aCursor.
     self allViewsDo:[:aView |  
-        dev := aView graphicsDevice.
-        dev notNil ifTrue:[
-            c := c onDevice:dev.
-            (cId := c id) notNil ifTrue:[
-               (vId := aView id) notNil ifTrue:[
-                    dev setCursor:cId in:vId.
-                ]
-            ]
-        ]
+	dev := aView graphicsDevice.
+	dev notNil ifTrue:[
+	    c := c onDevice:dev.
+	    (cId := c id) notNil ifTrue:[
+	       (vId := aView id) notNil ifTrue:[
+		    dev setCursor:cId in:vId.
+		]
+	    ]
+	]
     ].
 
     "Modified: / 22.4.1998 / 14:26:45 / cg"
@@ -1716,7 +1727,7 @@
 
     dev := self graphicsDevice.   
     dev isNil ifTrue:[
-        ^ aBlock value
+	^ aBlock value
     ].
 
     deviceCursor := aCursor onDevice:dev.
@@ -1726,39 +1737,39 @@
     "
     oldCursors := IdentityDictionary new.
     self allViewsDo:[:aView |
-        |old|
+	|old|
 
-        old := aView cursor.
-        old ~~ aCursor ifTrue:[
-            oldCursors at:aView put:old.
-            aView cursor:deviceCursor now:false
-        ]
+	old := aView cursor.
+	old ~~ aCursor ifTrue:[
+	    oldCursors at:aView put:old.
+	    aView cursor:deviceCursor now:false
+	]
     ].
 
     oldCursors size == 0 ifTrue:[
-        action := aBlock
+	action := aBlock
     ] ifFalse:[
-        action := [
-                    |rslt|
+	action := [
+		    |rslt|
 
-                    "/
-                    "/ here sync looks better; flush leads to almost invisible cursors when accepting.
-                    "/ I dont really know why (maybe unix does not context-switch to the Xserver
-                    "/ early enough after the requests have been sent ?)
-                    "/
-                    dev sync.
+		    "/
+		    "/ here sync looks better; flush leads to almost invisible cursors when accepting.
+		    "/ I dont really know why (maybe unix does not context-switch to the Xserver
+		    "/ early enough after the requests have been sent ?)
+		    "/
+		    dev sync.
 
-                    rslt := aBlock valueNowOrOnUnwindDo:[
-                        "
-                         restore cursors from the mapping
-                        "
-                        oldCursors keysAndValuesDo:[:view :cursor |
-                            view cursor:cursor now:false.
-                        ].
-                        dev flush
-                    ].
-                    rslt
-                  ]
+		    rslt := aBlock valueNowOrOnUnwindDo:[
+			"
+			 restore cursors from the mapping
+			"
+			oldCursors keysAndValuesDo:[:view :cursor |
+			    view cursor:cursor now:false.
+			].
+			dev flush
+		    ].
+		    rslt
+		  ]
     ].
 
 "/    (self isModal and:[previousGroup notNil]) ifTrue:[
@@ -1841,6 +1852,6 @@
 !WindowGroup class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/WindowGroup.st,v 1.144 1998-09-18 15:12:34 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/WindowGroup.st,v 1.145 1998-09-24 10:02:31 cg Exp $'
 ! !
 WindowGroup initialize!