new focus mechanism
authorClaus Gittinger <cg@exept.de>
Sun, 23 May 1999 14:48:40 +0200
changeset 2723 3e54762a7840
parent 2722 6fa197cfc572
child 2724 a8d2a8723791
new focus mechanism
WGroup.st
WindowGroup.st
--- a/WGroup.st	Sun May 23 14:06:27 1999 +0200
+++ b/WGroup.st	Sun May 23 14:48:40 1999 +0200
@@ -15,7 +15,7 @@
 		focusSequence preEventHook postEventHook pointerView
 		isForModalSubview focusByTab groupHasFocus'
 	classVariableNames:'LastActiveGroup LastActiveProcess LeaveSignal
-		WindowGroupQuerySignal LastEventQuerySignal FocusViewPerDisplay'
+		WindowGroupQuerySignal LastEventQuerySignal'
 	poolDictionaries:''
 	category:'Interface-Support'
 !
@@ -82,11 +82,11 @@
     and all of its subviews. However, this is not strictly required; 
     it is possible to create extra windowgroups for subviews, which will let them
     run in parallel 
-        (for example, the FileBrowsers kill-Button is created that 
-         way, to allow a kill of an executing unix command, while the browser 
-         itself reads the pipeStream for incoming text.
-         Even if the fileBrowser is busy reading the pipe, the killButton is still
-         working and allows terminating the pipe-read action).
+	(for example, the FileBrowsers kill-Button is created that 
+	 way, to allow a kill of an executing unix command, while the browser 
+	 itself reads the pipeStream for incoming text.
+	 Even if the fileBrowser is busy reading the pipe, the killButton is still
+	 working and allows terminating the pipe-read action).
 
     On the other hand, multiple topviews can be placed into the same windowGroup;
     which allows for multiview applications, of which only one communicates with
@@ -114,88 +114,86 @@
     events etc.
 
     Dont get confused:
-        You dont have to care for details in the normal case, a windowgroup is
-        created for you automatically, when a view is opened.
-        All of the internals are not required to be known for most applications.
+	You dont have to care for details in the normal case, a windowgroup is
+	created for you automatically, when a view is opened.
+	All of the internals are not required to be known for most applications.
 
 
     [instance variables:]
 
-        views                   collection of views of this group
+	views                   collection of views of this group
 
-        topViews                collection of topviews of this group
+	topViews                collection of topviews of this group
 
-        myProcess               the process executing the events
+	myProcess               the process executing the events
 
-        mySensor                my input sensor
+	mySensor                my input sensor
 
-        isModal                 true if this is for a modal box
+	isModal                 true if this is for a modal box
 
-        previousGroup           if modal, the group that started this one
+	previousGroup           if modal, the group that started this one
 
-        focusView               the one that has the keyboard focus (or nil)
+	focusView               the one that has the keyboard focus (or nil)
 
-        focusByTab              if focus came via tabbing 
-                                (as opposed to an implicit focus change)
+	focusByTab              if focus came via tabbing 
+				(as opposed to an implicit focus change)
                                 
-        focusSequence           defines the focus sequence
+	focusSequence           defines the focus sequence
 
-        preEventHook            if non-nil, that one gets notified of incoming
-                                events BEFORE an event is dispatched.
-                                May eat events (i.e. suppress dispatch)
-                                (hook for event filters or recorders)
+	preEventHook            if non-nil, that one gets notified of incoming
+				events BEFORE an event is dispatched.
+				May eat events (i.e. suppress dispatch)
+				(hook for event filters or recorders)
 
-        postEventHook           if non-nil, that one gets notified
-                                AFTER an event was dispatched.
+	postEventHook           if non-nil, that one gets notified
+				AFTER an event was dispatched.
 
-        isForModalSubView
+	isForModalSubView
 
-        groupHasFocus           true, if this windowGroup has the focus
+	groupHasFocus           true, if this windowGroup has the focus
 
 
     [class variables:]
-        LeaveSignal             if raised, a modal box leaves (closes)
+	LeaveSignal             if raised, a modal box leaves (closes)
 
-        WindowGroupQuerySignal  to ask for the current windowGroup,
-                                anywhere in the program, simply raise this
-                                signal. The raise returns nil, for processes,
-                                which are not under control of a windowGroup.
-                                (i.e. wg := WindowGroup windowGroupQuerySignal raise)
+	WindowGroupQuerySignal  to ask for the current windowGroup,
+				anywhere in the program, simply raise this
+				signal. The raise returns nil, for processes,
+				which are not under control of a windowGroup.
+				(i.e. wg := WindowGroup windowGroupQuerySignal raise)
 
-        LastEventQuerySignal    to ask for the event which was responsible
-                                for being where you are (whereever that is).
-                                The raise returns nil, if you did not arrive
-                                there due to an event.
-                                (i.e. ev := WindowGroup lastEventQuerySignal raise)
-                                The event can be asked for the view, the type
-                                of event, x/y position etc.
-
-        FocusViewPerDisplay     the view which has the focus (global - per display).
+	LastEventQuerySignal    to ask for the event which was responsible
+				for being where you are (whereever that is).
+				The raise returns nil, if you did not arrive
+				there due to an event.
+				(i.e. ev := WindowGroup lastEventQuerySignal raise)
+				The event can be asked for the view, the type
+				of event, x/y position etc.
 
 
     (*) 
-        due to historic reasons, many views have the controller functionality
-        integrated, and handle events themself. The windowSensor takes care
-        of this, by checking if a view has a controller, and, if so, forwarding 
-        the events to it. Otherwise, events are sent directly to the view.
+	due to historic reasons, many views have the controller functionality
+	integrated, and handle events themself. The windowSensor takes care
+	of this, by checking if a view has a controller, and, if so, forwarding 
+	the events to it. Otherwise, events are sent directly to the view.
 
-        In the future, all views will be rewritten to actually use a controller.
-        Currently (being in the middle of this migration), only some views
-        (buttons, toggles and subclasses) do so.
+	In the future, all views will be rewritten to actually use a controller.
+	Currently (being in the middle of this migration), only some views
+	(buttons, toggles and subclasses) do so.
 
     For more information, read 'introduction to view programming' in the
     doc/online directory.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        WindowSensor WindowEvent EventListener KeyboardForwarder
-        DeviceWorkstation
-        View StandardSystemView
-        ApplicationModel
-        Process ProcessorScheduler
-        (``Working with processes (programmers manual)'': programming/processes.html#VIEWSNPROCS)
+	WindowSensor WindowEvent EventListener KeyboardForwarder
+	DeviceWorkstation
+	View StandardSystemView
+	ApplicationModel
+	Process ProcessorScheduler
+	(``Working with processes (programmers manual)'': programming/processes.html#VIEWSNPROCS)
 "
 ! !
 
@@ -203,21 +201,19 @@
 
 initialize
     LeaveSignal isNil ifTrue:[
-        LeaveSignal := (Signal new) mayProceed:true.
-        LeaveSignal nameClass:self message:#leaveSignal.
-        LeaveSignal notifierString:'unhandled leave signal'.
+	LeaveSignal := (Signal new) mayProceed:true.
+	LeaveSignal nameClass:self message:#leaveSignal.
+	LeaveSignal notifierString:'unhandled leave signal'.
 
-        WindowGroupQuerySignal := QuerySignal new.
-        WindowGroupQuerySignal nameClass:self message:#windowGroupQuerySignal.
-        WindowGroupQuerySignal notifierString:'query for windowgroup'.
+	WindowGroupQuerySignal := QuerySignal new.
+	WindowGroupQuerySignal nameClass:self message:#windowGroupQuerySignal.
+	WindowGroupQuerySignal notifierString:'query for windowgroup'.
 
-        LastEventQuerySignal := QuerySignal new.
-        LastEventQuerySignal nameClass:self message:#lastEventQuerySignal.
-        LastEventQuerySignal notifierString:'query for last event'.
+	LastEventQuerySignal := QuerySignal new.
+	LastEventQuerySignal nameClass:self message:#lastEventQuerySignal.
+	LastEventQuerySignal notifierString:'query for last event'.
     ].
 
-    FocusViewPerDisplay := IdentityDictionary new.
-
     "WindowGroup initialize"
 
     "Modified: 9.11.1996 / 17:00:53 / cg"
@@ -283,31 +279,31 @@
     activeProcess := Processor activeProcess.
     " caching the last value ..."
     activeProcess == LastActiveProcess ifTrue:[
-        LastActiveGroup process == LastActiveProcess ifTrue:[
-            ^ LastActiveGroup
-        ]
+	LastActiveGroup process == LastActiveProcess ifTrue:[
+	    ^ LastActiveGroup
+	]
     ].
 
     wg := WindowGroupQuerySignal query.
 
     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
 
@@ -360,6 +356,27 @@
     LastActiveGroup := aGroup
 ! !
 
+!WindowGroup class methodsFor:'focus control support'!
+
+takeFocusFromDevice:aDevice
+    |prevFocusView prevFocusGroup prevFocusCameViaTab|
+
+    "/
+    "/ take the focus from whichEver view had it previously
+    "/
+    prevFocusView := aDevice focusView.
+    prevFocusView notNil ifTrue:[
+	(prevFocusView notNil
+	and:[(prevFocusGroup := prevFocusView windowGroup) notNil]) ifTrue:[
+	    prevFocusCameViaTab := prevFocusGroup focusCameByTab.
+
+	    prevFocusView showNoFocus:prevFocusCameViaTab. "/ true is bad - see pullDownMenu.
+	    prevFocusView hasKeyboardFocus:false.
+	].
+    ].
+    aDevice focusView:nil.
+! !
+
 !WindowGroup methodsFor:'accessing'!
 
 device
@@ -540,11 +557,11 @@
     "add a topview to the group"
 
     topViews isNil ifTrue:[
-        topViews := OrderedCollection with:aView.
+	topViews := OrderedCollection with:aView.
     ] ifFalse:[
-        (topViews includesIdentical:aView) ifFalse:[
-            topViews add:aView
-        ]
+	(topViews includesIdentical:aView) ifFalse:[
+	    topViews add:aView
+	]
     ]
 
     "Modified: 6.3.1996 / 15:35:15 / cg"
@@ -554,11 +571,11 @@
     "add aView to the windowGroup"
 
     views isNil ifTrue:[
-        views := OrderedCollection with:aView.
+	views := OrderedCollection with:aView.
     ] ifFalse:[
-        (views includesIdentical:aView) ifFalse:[
-            views add:aView
-        ]
+	(views includesIdentical:aView) ifFalse:[
+	    views add:aView
+	]
     ]
 
     "Modified: 6.3.1996 / 15:35:41 / cg"
@@ -581,25 +598,25 @@
     |sema|
 
     views notNil ifTrue:[
-        views removeIdentical:aView ifAbsent:nil.
-        views isEmpty ifTrue:[
-            views := nil
-        ]
+	views removeIdentical:aView ifAbsent:nil.
+	views isEmpty ifTrue:[
+	    views := nil
+	]
     ].
     topViews notNil ifTrue:[
-        topViews removeIdentical:aView ifAbsent:nil.
-        topViews isEmpty ifTrue:[
-            topViews := nil
-        ]
+	topViews removeIdentical:aView ifAbsent:nil.
+	topViews isEmpty ifTrue:[
+	    topViews := nil
+	]
     ].
     "
      wakeup my process to look if last view has been
      removed (modalBoxes terminate their modalLoop if so)
     "
     mySensor notNil ifTrue:[
-        (sema := mySensor eventSemaphore) notNil ifTrue:[
-            sema signal
-        ]
+	(sema := mySensor eventSemaphore) notNil ifTrue:[
+	    sema signal
+	]
     ]
 
     "Modified: 1.2.1997 / 12:13:26 / cg"
@@ -623,11 +640,11 @@
     "destroy all views associated to this window group"
 
     topViews notNil ifTrue:[
-        topViews do:[:aTopView | 
-            aTopView notNil ifTrue:[
-                aTopView destroy
-            ]
-        ]
+	topViews do:[:aTopView | 
+	    aTopView notNil ifTrue:[
+		aTopView destroy
+	    ]
+	]
     ].
     views := nil.
     topViews := nil.
@@ -654,14 +671,14 @@
      my views."
 
     topViews notNil ifTrue:[
-        "
-         need a new semaphore, since obsolete processes 
-         (from our previous live) may still sit on the current semaphore
-        "
-        mySensor eventSemaphore:(Semaphore new name:'WGroup eventSema').
-        isModal ifFalse:[
-            self startupWith:[self restartTopViews].
-        ]
+	"
+	 need a new semaphore, since obsolete processes 
+	 (from our previous live) may still sit on the current semaphore
+	"
+	mySensor eventSemaphore:(Semaphore new name:'WGroup eventSema').
+	isModal ifFalse:[
+	    self startupWith:[self restartTopViews].
+	]
     ]
 
     "Modified: / 6.5.1999 / 09:46:08 / cg"
@@ -672,12 +689,12 @@
      about the restart."
 
     topViews notNil ifTrue:[
-        topViews do:[:aView |
-            aView isPopUpView ifFalse:[
+	topViews do:[:aView |
+	    aView isPopUpView ifFalse:[
 "/                aView realize.
-                aView restarted
-            ].
-        ].
+		aView restarted
+	    ].
+	].
     ].
 
     "Modified: / 6.5.1999 / 09:42:37 / cg"
@@ -956,172 +973,172 @@
      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].
 
-                (mainGroup notNil or:[mySensor hasEvents not]) ifTrue:[
-                    "/ now, wait for an event to arrive
-                    thisProcess setStateTo:#eventWait if:#active.
-                    waitSema isNil ifTrue:[
-                        "/ oops - how can this happen ....
-                        ^ self.
-                    ].
-                    gotSema := waitSema wait.
-                ] ifFalse:[
-                    gotSema := mySema
-                ].
-                LastActiveGroup := self.
-                LastActiveProcess := thisProcess.
+		(mainGroup notNil or:[mySensor hasEvents not]) ifTrue:[
+		    "/ now, wait for an event to arrive
+		    thisProcess setStateTo:#eventWait if:#active.
+		    waitSema isNil ifTrue:[
+			"/ oops - how can this happen ....
+			^ self.
+		    ].
+		    gotSema := waitSema wait.
+		] ifFalse:[
+		    gotSema := mySema
+		].
+		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"
@@ -1157,51 +1174,51 @@
     self processExposeEvents.
 
     LastEventQuerySignal handle:[:ex |
-        ex proceedWith:event
+	ex proceedWith:event
     ] do:[
-        [mySensor notNil
-         and:[(event := mySensor nextEvent) notNil]] whileTrue:[
-            ignore := false.
-            focus := focusView.
-            modalDelegate := false.
-            modalTop := nil.
+	[mySensor notNil
+	 and:[(event := mySensor nextEvent) notNil]] whileTrue:[
+	    ignore := false.
+	    focus := focusView.
+	    modalDelegate := false.
+	    modalTop := nil.
 
-            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.
-                    ].
-                    modalGroup focusView notNil ifTrue:[
-                        focus := modalGroup focusView
-                    ]
-                ] ifFalse:[
-                    event isFocusEvent ifTrue:[
-                        event isFocusInEvent ifTrue:[
-                            "/ move focus over to modalBox
-                            modalTop notNil ifTrue:[
-                                modalTop getKeyboardFocus.
-                                "/ 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.
+		    ].
+		    modalGroup focusView notNil ifTrue:[
+			focus := modalGroup focusView
+		    ]
+		] ifFalse:[
+		    event isFocusEvent ifTrue:[
+			event isFocusInEvent ifTrue:[
+			    "/ move focus over to modalBox
+			    modalTop notNil ifTrue:[
+				modalTop getKeyboardFocus.
+				"/ 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.
@@ -1211,112 +1228,112 @@
 "/                                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:[
+	    ignore ifFalse:[
+		(views notNil or:[topViews notNil]) ifTrue:[
 
-                    "/ give eventRecorders, catchers etc. 
-                    "/ a chance to eat or modify that event
+		    "/ give eventRecorders, catchers etc. 
+		    "/ a chance to eat or modify that event
 
-                    (preEventHook  notNil 
-                    and:[preEventHook processEvent:event]) ifTrue:[
-                        ignore := true.
-                    ].
+		    (preEventHook  notNil 
+		    and:[preEventHook processEvent:event]) ifTrue:[
+			ignore := true.
+		    ].
 
-                    ignore ifFalse:[
-                        evView := event view.
+		    ignore ifFalse:[
+			evView := event view.
 
-                        (event isKeyEvent 
-                        and:[(keyboardProcessor := (modalTop ? evView topView) keyboardProcessor) notNil]) ifTrue:[
-                            ignore := keyboardProcessor processEvent:event forModalView:modalTop
-                        ].
-                    ].
+			(event isKeyEvent 
+			and:[(keyboardProcessor := (modalTop ? evView topView) keyboardProcessor) notNil]) ifTrue:[
+			    ignore := keyboardProcessor processEvent:event forModalView:modalTop
+			].
+		    ].
 
-                    ignore ifFalse:[
-                        "/ event handling below will vanish ...
-                        "/ (keyboardProcessor will do it)
+		    ignore ifFalse:[
+			"/ event handling below will vanish ...
+			"/ (keyboardProcessor will do it)
 
-                        event isKeyPressEvent ifTrue:[
-                            event 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
-                                ]
-                            ]
-                        ].
+			event isKeyPressEvent ifTrue:[
+			    event 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 reverts
-                        "/ to implicit focus control
-                        "/ This used to be done for every click -
-                        "/ but behaved ugly if clicking in a scrollbar ...
+			"/
+			"/ buttonPress events turn off explicit focus, and reverts
+			"/ to implicit focus control
+			"/ This used to be done for every click -
+			"/ but behaved ugly if clicking in a scrollbar ...
 
-                        event isButtonPressEvent ifTrue:[
-                            (evView wantsFocusWithButtonPress) ifTrue:[
-                                self focusView:evView.
-                            ].
-                        ].
+			event isButtonPressEvent ifTrue:[
+			    (evView wantsFocusWithButtonPress) ifTrue:[
+				self focusView:evView.
+			    ].
+			].
 
-                        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
+			]
+		    ].
 
-                    "/ give eventRecorders, postProcessors 
-                    "/ a chance to see that event
+		    "/ give eventRecorders, postProcessors 
+		    "/ a chance to see that event
 
-                    postEventHook notNil ifTrue:[
-                        postEventHook processEvent:event
-                    ].
-                ]
-            ].
-        ]
+		    postEventHook notNil ifTrue:[
+			postEventHook processEvent:event
+		    ].
+		]
+	    ].
+	]
     ]
 
     "Created: / 5.3.1997 / 11:33:11 / cg"
@@ -1338,44 +1355,44 @@
 
     (sensor := mySensor) isNil ifTrue:[^ self].
     (sensor damageCount ~~ 0) ifTrue:[
-        thisProcess := Processor activeProcess.
+	thisProcess := Processor activeProcess.
 
-        [(event := sensor nextDamageEventFor:aViewOrNil) notNil] whileTrue:[
-            LastActiveGroup := self.
-            LastActiveProcess := thisProcess.
+	[(event := sensor nextDamageEventFor:aViewOrNil) notNil] whileTrue:[
+	    LastActiveGroup := self.
+	    LastActiveProcess := thisProcess.
 
-            (views notNil or:[topViews notNil]) ifTrue:[
-                view := event view.
-                (aViewOrNil isNil or:[aViewOrNil == view]) ifTrue:[
-                    LastEventQuerySignal handle:[:ex |
-                        ex proceedWith:event
-                    ] do:[
-                        (preEventHook notNil 
-                        and:[preEventHook processEvent:event]) ifFalse:[
-                            "/
-                            "/ if the view is no longer shown (iconified or closed),
-                            "/ this is a leftover event and ignored.
-                            "/
-                            "/ could this ever be a non-damage ?
-                            "/
-                            (view shown or:[event isDamage not]) ifTrue:[
-                                LastActiveGroup := self.
-                                LastActiveProcess := thisProcess.
+	    (views notNil or:[topViews notNil]) ifTrue:[
+		view := event view.
+		(aViewOrNil isNil or:[aViewOrNil == view]) ifTrue:[
+		    LastEventQuerySignal handle:[:ex |
+			ex proceedWith:event
+		    ] do:[
+			(preEventHook notNil 
+			and:[preEventHook processEvent:event]) ifFalse:[
+			    "/
+			    "/ if the view is no longer shown (iconified or closed),
+			    "/ this is a leftover event and ignored.
+			    "/
+			    "/ could this ever be a non-damage ?
+			    "/
+			    (view shown or:[event isDamage not]) ifTrue:[
+				LastActiveGroup := self.
+				LastActiveProcess := thisProcess.
 
-                                view
-                                    dispatchEvent:(event type) 
-                                    arguments:(event arguments) 
-                                    withFocusOn:nil 
-                                    delegate:true
-                            ].
-                        ]
-                    ].
-                    postEventHook notNil ifTrue:[
-                        postEventHook processEvent:event
-                    ]
-                ]
-            ]
-        ]
+				view
+				    dispatchEvent:(event type) 
+				    arguments:(event arguments) 
+				    withFocusOn:nil 
+				    delegate:true
+			    ].
+			]
+		    ].
+		    postEventHook notNil ifTrue:[
+			postEventHook processEvent:event
+		    ]
+		]
+	    ]
+	]
     ]
 
     "Created: / 3.12.1998 / 14:01:39 / cg"
@@ -1499,33 +1516,33 @@
 
     sequence := self focusSequence.
     (lastIndex := sequence size) == 0 ifTrue:[
-        ^ self
+	^ self
     ].
 
     focusView isNil ifTrue:[
-        index := 0
+	index := 0
     ] ifFalse:[
-        index := index0 := self indexOfFocusViewInFocusSequence.
+	index := index0 := self indexOfFocusViewInFocusSequence.
     ].
 
     [next isNil] whileTrue:[
-        index := index + 1.
-        index > lastIndex ifTrue:[
-            index := 1.
-            index0 isNil ifTrue:[^ self ].
-        ].
-        index == index0 ifTrue:[
-            ^ self
-        ].
+	index := index + 1.
+	index > lastIndex ifTrue:[
+	    index := 1.
+	    index0 isNil ifTrue:[^ self ].
+	].
+	index == index0 ifTrue:[
+	    ^ self
+	].
 
-        next := (sequence at:index).
-        next realized not ifTrue:[
-            next := nil
-        ] ifFalse:[
-            next enabled ifFalse:[
-                next := nil
-            ]
-        ]
+	next := (sequence at:index).
+	next realized not ifTrue:[
+	    next := nil
+	] ifFalse:[
+	    next enabled ifFalse:[
+		next := nil
+	    ]
+	]
     ].
 
     self focusView:next byTab:true
@@ -1566,31 +1583,31 @@
     (lastIndex := sequence size) == 0 ifTrue:[^ self].
 
     focusView isNil ifTrue:[
-        index := 0
+	index := 0
     ] ifFalse:[
-        index := self indexOfFocusViewInFocusSequence.
-        index0 := index.
+	index := self indexOfFocusViewInFocusSequence.
+	index0 := index.
     ].
     index == 0 ifTrue:[
-        index := lastIndex + 1.
+	index := lastIndex + 1.
     ].
 
     [prev isNil] whileTrue:[
-        index := index - 1.
-        index < 1 ifTrue:[
-            index := lastIndex.
-            index0 isNil ifTrue:[^ self].
-        ].
-        index == index0 ifTrue:[^ self].
+	index := index - 1.
+	index < 1 ifTrue:[
+	    index := lastIndex.
+	    index0 isNil ifTrue:[^ self].
+	].
+	index == index0 ifTrue:[^ self].
 
-        prev := (sequence at:index).
-        prev realized not ifTrue:[
-            prev := nil
-        ] ifFalse:[
-            prev enabled ifFalse:[
-                prev := nil
-            ]
-        ].
+	prev := (sequence at:index).
+	prev realized not ifTrue:[
+	    prev := nil
+	] ifFalse:[
+	    prev enabled ifFalse:[
+		prev := nil
+	    ]
+	].
     ].
 
     self focusView:prev byTab:true
@@ -1618,27 +1635,23 @@
     myDisplay := self graphicsDevice.
     (myDisplay notNil 
     and:[myDisplay activateOnClick:nil]) ifTrue:[
-        i := FocusViewPerDisplay at:myDisplay ifAbsent:nil.
-        i notNil ifTrue:[
-            prevFocusView := i key.
-        ].
-
-        (prevFocusView notNil 
-        and:[prevFocusView windowGroup ~~ aView windowGroup]) ifTrue:[
-            "/ a view from another windowGroup requests the focus.
-            "/ Do not grant this, if in windows-activateOnClick mode.
+	prevFocusView := myDisplay focusView.
+	(prevFocusView notNil 
+	and:[prevFocusView windowGroup ~~ aView windowGroup]) ifTrue:[
+	    "/ a view from another windowGroup requests the focus.
+	    "/ Do not grant this, if in windows-activateOnClick mode.
 
 "/            ' not granted' printCR.
-            myDisplay setInputFocusTo:prevFocusView.
-            ^ false
-        ].
+	    myDisplay setInputFocusTo:prevFocusView.
+	    ^ false
+	].
     ].
 
 "/    ' granted' printCR.
 
     (focusView isNil or:[focusByTab not]) ifTrue:[
-        self focusView:aView byTab:false.
-        ^ true
+	self focusView:aView byTab:false.
+	^ true
     ].
     ^ false
 
@@ -1685,18 +1698,18 @@
     |seq doAssignFocusView|
 
     focusView == aViewOrNil ifFalse:[
-        doAssignFocusView := false.
-        topViews isNil ifTrue:[
-            "/ mhmh - a topview-less windowGroup
-            doAssignFocusView := true.
-        ] ifFalse:[
-            (seq := self focusSequence) notNil ifTrue:[
-                doAssignFocusView := (seq includesIdentical:aViewOrNil).
-            ]
-        ].
-        doAssignFocusView ifTrue:[
-            self focusView:aViewOrNil.
-        ]
+	doAssignFocusView := false.
+	topViews isNil ifTrue:[
+	    "/ mhmh - a topview-less windowGroup
+	    doAssignFocusView := true.
+	] ifFalse:[
+	    (seq := self focusSequence) notNil ifTrue:[
+		doAssignFocusView := (seq includesIdentical:aViewOrNil).
+	    ]
+	].
+	doAssignFocusView ifTrue:[
+	    self focusView:aViewOrNil.
+	]
     ]
 
     "Created: / 18.9.1998 / 16:28:27 / cg"
@@ -1733,57 +1746,50 @@
      If it came via tabbing, the view is notified differently, to allow
      for special highlighting (i.e. drawing a focus-border around itself)"
 
-    |i prevFocusView prevFocusCameViaTab myDisplay|
+    |i prevFocusView myDisplay|
 
 "/  'focusToView:' print. aViewOrNil printCR. 
 
     myDisplay := self graphicsDevice.
     myDisplay notNil ifTrue:[
-        "/
-        "/ take the focus from whichEver view had it previously
-        "/
-        i := FocusViewPerDisplay at:myDisplay ifAbsent:nil.
-        i notNil ifTrue:[
-            prevFocusView := i key.
-            prevFocusCameViaTab := i value
-        ].
-
-        (prevFocusView notNil 
-        and:[prevFocusView ~~ aViewOrNil]) ifTrue:[
-            prevFocusView showNoFocus:prevFocusCameViaTab. "/ true is bad - see pullDownMenu.
-            prevFocusView hasKeyboardFocus:false.
-        ].
-        FocusViewPerDisplay at:myDisplay put:(aViewOrNil->focusCameViaTab).
+	"/
+	"/ take the focus from whichEver view had it previously
+	"/
+	prevFocusView := myDisplay focusView.
+	prevFocusView ~~ aViewOrNil ifTrue:[
+	    self class takeFocusFromDevice:myDisplay.
+	].
+	myDisplay focusView:aViewOrNil.
     ].
 
     focusView == aViewOrNil ifTrue:[
-        focusView notNil ifTrue:[
-            "/ this is the case when the mouse-pointer reenters
-            "/ into a topView which had a focusView
-            focusByTab := focusCameViaTab or:[focusByTab].
-            focusView showFocus:focusByTab.
-            aViewOrNil hasKeyboardFocus:true.
-            FocusViewPerDisplay at:myDisplay put:(aViewOrNil->focusByTab).
-        ].
-        ^ self
+	focusView notNil ifTrue:[
+	    "/ this is the case when the mouse-pointer reenters
+	    "/ into a topView which had a focusView
+	    focusByTab := focusCameViaTab or:[focusByTab].
+	    focusView showFocus:focusByTab.
+	    aViewOrNil hasKeyboardFocus:true.
+	    myDisplay focusView:aViewOrNil.
+	].
+	^ self
     ].
 
     focusView notNil ifTrue:[
-        "/ lost explicit focus
-        focusView == aViewOrNil ifTrue:[
-            aViewOrNil hasKeyboardFocus:true.
-            FocusViewPerDisplay at:myDisplay put:(aViewOrNil->focusCameViaTab).
-            ^ self
-        ].
+	"/ lost explicit focus
+	focusView == aViewOrNil ifTrue:[
+	    aViewOrNil hasKeyboardFocus:true.
+	    myDisplay focusView:aViewOrNil.
+	    ^ self
+	].
     ].
 
     focusView := aViewOrNil.
     focusView notNil ifTrue:[
-        "/ got explicit focus
-        aViewOrNil showFocus:focusCameViaTab.
-        aViewOrNil hasKeyboardFocus:true.
-        focusByTab := focusCameViaTab.
-        FocusViewPerDisplay at:myDisplay put:(aViewOrNil->focusCameViaTab).
+	"/ got explicit focus
+	aViewOrNil showFocus:focusCameViaTab.
+	aViewOrNil hasKeyboardFocus:true.
+	focusByTab := focusCameViaTab.
+	myDisplay focusView:aViewOrNil.
     ].
 
     "
@@ -1808,20 +1814,20 @@
     sequence := self focusSequence.
 
     focusView notNil ifTrue:[
-        index := (sequence identityIndexOf:focusView).
-        index == 0 ifTrue:[
-            "/ mhmh - how comes ?
-            "/ (in rare cases, a subwidget of one of my 
-            "/  focusSequence-widgets has the focus.
-            "/  in that case, care for this here)
-            v := focusView superView.
-            [index == 0 and:[v notNil]] whileTrue:[
-                index := (sequence identityIndexOf:v).
-                v := v superView
-            ].
-        ]
+	index := (sequence identityIndexOf:focusView).
+	index == 0 ifTrue:[
+	    "/ mhmh - how comes ?
+	    "/ (in rare cases, a subwidget of one of my 
+	    "/  focusSequence-widgets has the focus.
+	    "/  in that case, care for this here)
+	    v := focusView superView.
+	    [index == 0 and:[v notNil]] whileTrue:[
+		index := (sequence identityIndexOf:v).
+		v := v superView
+	    ].
+	]
     ] ifFalse:[
-        index := 0.
+	index := 0.
     ].
     ^ index
 ! !
@@ -2068,6 +2074,6 @@
 !WindowGroup class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/Attic/WGroup.st,v 1.174 1999-05-20 16:35:21 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/Attic/WGroup.st,v 1.175 1999-05-23 12:48:40 cg Exp $'
 ! !
 WindowGroup initialize!
--- a/WindowGroup.st	Sun May 23 14:06:27 1999 +0200
+++ b/WindowGroup.st	Sun May 23 14:48:40 1999 +0200
@@ -15,7 +15,7 @@
 		focusSequence preEventHook postEventHook pointerView
 		isForModalSubview focusByTab groupHasFocus'
 	classVariableNames:'LastActiveGroup LastActiveProcess LeaveSignal
-		WindowGroupQuerySignal LastEventQuerySignal FocusViewPerDisplay'
+		WindowGroupQuerySignal LastEventQuerySignal'
 	poolDictionaries:''
 	category:'Interface-Support'
 !
@@ -82,11 +82,11 @@
     and all of its subviews. However, this is not strictly required; 
     it is possible to create extra windowgroups for subviews, which will let them
     run in parallel 
-        (for example, the FileBrowsers kill-Button is created that 
-         way, to allow a kill of an executing unix command, while the browser 
-         itself reads the pipeStream for incoming text.
-         Even if the fileBrowser is busy reading the pipe, the killButton is still
-         working and allows terminating the pipe-read action).
+	(for example, the FileBrowsers kill-Button is created that 
+	 way, to allow a kill of an executing unix command, while the browser 
+	 itself reads the pipeStream for incoming text.
+	 Even if the fileBrowser is busy reading the pipe, the killButton is still
+	 working and allows terminating the pipe-read action).
 
     On the other hand, multiple topviews can be placed into the same windowGroup;
     which allows for multiview applications, of which only one communicates with
@@ -114,88 +114,86 @@
     events etc.
 
     Dont get confused:
-        You dont have to care for details in the normal case, a windowgroup is
-        created for you automatically, when a view is opened.
-        All of the internals are not required to be known for most applications.
+	You dont have to care for details in the normal case, a windowgroup is
+	created for you automatically, when a view is opened.
+	All of the internals are not required to be known for most applications.
 
 
     [instance variables:]
 
-        views                   collection of views of this group
+	views                   collection of views of this group
 
-        topViews                collection of topviews of this group
+	topViews                collection of topviews of this group
 
-        myProcess               the process executing the events
+	myProcess               the process executing the events
 
-        mySensor                my input sensor
+	mySensor                my input sensor
 
-        isModal                 true if this is for a modal box
+	isModal                 true if this is for a modal box
 
-        previousGroup           if modal, the group that started this one
+	previousGroup           if modal, the group that started this one
 
-        focusView               the one that has the keyboard focus (or nil)
+	focusView               the one that has the keyboard focus (or nil)
 
-        focusByTab              if focus came via tabbing 
-                                (as opposed to an implicit focus change)
+	focusByTab              if focus came via tabbing 
+				(as opposed to an implicit focus change)
                                 
-        focusSequence           defines the focus sequence
+	focusSequence           defines the focus sequence
 
-        preEventHook            if non-nil, that one gets notified of incoming
-                                events BEFORE an event is dispatched.
-                                May eat events (i.e. suppress dispatch)
-                                (hook for event filters or recorders)
+	preEventHook            if non-nil, that one gets notified of incoming
+				events BEFORE an event is dispatched.
+				May eat events (i.e. suppress dispatch)
+				(hook for event filters or recorders)
 
-        postEventHook           if non-nil, that one gets notified
-                                AFTER an event was dispatched.
+	postEventHook           if non-nil, that one gets notified
+				AFTER an event was dispatched.
 
-        isForModalSubView
+	isForModalSubView
 
-        groupHasFocus           true, if this windowGroup has the focus
+	groupHasFocus           true, if this windowGroup has the focus
 
 
     [class variables:]
-        LeaveSignal             if raised, a modal box leaves (closes)
+	LeaveSignal             if raised, a modal box leaves (closes)
 
-        WindowGroupQuerySignal  to ask for the current windowGroup,
-                                anywhere in the program, simply raise this
-                                signal. The raise returns nil, for processes,
-                                which are not under control of a windowGroup.
-                                (i.e. wg := WindowGroup windowGroupQuerySignal raise)
+	WindowGroupQuerySignal  to ask for the current windowGroup,
+				anywhere in the program, simply raise this
+				signal. The raise returns nil, for processes,
+				which are not under control of a windowGroup.
+				(i.e. wg := WindowGroup windowGroupQuerySignal raise)
 
-        LastEventQuerySignal    to ask for the event which was responsible
-                                for being where you are (whereever that is).
-                                The raise returns nil, if you did not arrive
-                                there due to an event.
-                                (i.e. ev := WindowGroup lastEventQuerySignal raise)
-                                The event can be asked for the view, the type
-                                of event, x/y position etc.
-
-        FocusViewPerDisplay     the view which has the focus (global - per display).
+	LastEventQuerySignal    to ask for the event which was responsible
+				for being where you are (whereever that is).
+				The raise returns nil, if you did not arrive
+				there due to an event.
+				(i.e. ev := WindowGroup lastEventQuerySignal raise)
+				The event can be asked for the view, the type
+				of event, x/y position etc.
 
 
     (*) 
-        due to historic reasons, many views have the controller functionality
-        integrated, and handle events themself. The windowSensor takes care
-        of this, by checking if a view has a controller, and, if so, forwarding 
-        the events to it. Otherwise, events are sent directly to the view.
+	due to historic reasons, many views have the controller functionality
+	integrated, and handle events themself. The windowSensor takes care
+	of this, by checking if a view has a controller, and, if so, forwarding 
+	the events to it. Otherwise, events are sent directly to the view.
 
-        In the future, all views will be rewritten to actually use a controller.
-        Currently (being in the middle of this migration), only some views
-        (buttons, toggles and subclasses) do so.
+	In the future, all views will be rewritten to actually use a controller.
+	Currently (being in the middle of this migration), only some views
+	(buttons, toggles and subclasses) do so.
 
     For more information, read 'introduction to view programming' in the
     doc/online directory.
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 
     [see also:]
-        WindowSensor WindowEvent EventListener KeyboardForwarder
-        DeviceWorkstation
-        View StandardSystemView
-        ApplicationModel
-        Process ProcessorScheduler
-        (``Working with processes (programmers manual)'': programming/processes.html#VIEWSNPROCS)
+	WindowSensor WindowEvent EventListener KeyboardForwarder
+	DeviceWorkstation
+	View StandardSystemView
+	ApplicationModel
+	Process ProcessorScheduler
+	(``Working with processes (programmers manual)'': programming/processes.html#VIEWSNPROCS)
 "
 ! !
 
@@ -203,21 +201,19 @@
 
 initialize
     LeaveSignal isNil ifTrue:[
-        LeaveSignal := (Signal new) mayProceed:true.
-        LeaveSignal nameClass:self message:#leaveSignal.
-        LeaveSignal notifierString:'unhandled leave signal'.
+	LeaveSignal := (Signal new) mayProceed:true.
+	LeaveSignal nameClass:self message:#leaveSignal.
+	LeaveSignal notifierString:'unhandled leave signal'.
 
-        WindowGroupQuerySignal := QuerySignal new.
-        WindowGroupQuerySignal nameClass:self message:#windowGroupQuerySignal.
-        WindowGroupQuerySignal notifierString:'query for windowgroup'.
+	WindowGroupQuerySignal := QuerySignal new.
+	WindowGroupQuerySignal nameClass:self message:#windowGroupQuerySignal.
+	WindowGroupQuerySignal notifierString:'query for windowgroup'.
 
-        LastEventQuerySignal := QuerySignal new.
-        LastEventQuerySignal nameClass:self message:#lastEventQuerySignal.
-        LastEventQuerySignal notifierString:'query for last event'.
+	LastEventQuerySignal := QuerySignal new.
+	LastEventQuerySignal nameClass:self message:#lastEventQuerySignal.
+	LastEventQuerySignal notifierString:'query for last event'.
     ].
 
-    FocusViewPerDisplay := IdentityDictionary new.
-
     "WindowGroup initialize"
 
     "Modified: 9.11.1996 / 17:00:53 / cg"
@@ -283,31 +279,31 @@
     activeProcess := Processor activeProcess.
     " caching the last value ..."
     activeProcess == LastActiveProcess ifTrue:[
-        LastActiveGroup process == LastActiveProcess ifTrue:[
-            ^ LastActiveGroup
-        ]
+	LastActiveGroup process == LastActiveProcess ifTrue:[
+	    ^ LastActiveGroup
+	]
     ].
 
     wg := WindowGroupQuerySignal query.
 
     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
 
@@ -360,6 +356,27 @@
     LastActiveGroup := aGroup
 ! !
 
+!WindowGroup class methodsFor:'focus control support'!
+
+takeFocusFromDevice:aDevice
+    |prevFocusView prevFocusGroup prevFocusCameViaTab|
+
+    "/
+    "/ take the focus from whichEver view had it previously
+    "/
+    prevFocusView := aDevice focusView.
+    prevFocusView notNil ifTrue:[
+	(prevFocusView notNil
+	and:[(prevFocusGroup := prevFocusView windowGroup) notNil]) ifTrue:[
+	    prevFocusCameViaTab := prevFocusGroup focusCameByTab.
+
+	    prevFocusView showNoFocus:prevFocusCameViaTab. "/ true is bad - see pullDownMenu.
+	    prevFocusView hasKeyboardFocus:false.
+	].
+    ].
+    aDevice focusView:nil.
+! !
+
 !WindowGroup methodsFor:'accessing'!
 
 device
@@ -540,11 +557,11 @@
     "add a topview to the group"
 
     topViews isNil ifTrue:[
-        topViews := OrderedCollection with:aView.
+	topViews := OrderedCollection with:aView.
     ] ifFalse:[
-        (topViews includesIdentical:aView) ifFalse:[
-            topViews add:aView
-        ]
+	(topViews includesIdentical:aView) ifFalse:[
+	    topViews add:aView
+	]
     ]
 
     "Modified: 6.3.1996 / 15:35:15 / cg"
@@ -554,11 +571,11 @@
     "add aView to the windowGroup"
 
     views isNil ifTrue:[
-        views := OrderedCollection with:aView.
+	views := OrderedCollection with:aView.
     ] ifFalse:[
-        (views includesIdentical:aView) ifFalse:[
-            views add:aView
-        ]
+	(views includesIdentical:aView) ifFalse:[
+	    views add:aView
+	]
     ]
 
     "Modified: 6.3.1996 / 15:35:41 / cg"
@@ -581,25 +598,25 @@
     |sema|
 
     views notNil ifTrue:[
-        views removeIdentical:aView ifAbsent:nil.
-        views isEmpty ifTrue:[
-            views := nil
-        ]
+	views removeIdentical:aView ifAbsent:nil.
+	views isEmpty ifTrue:[
+	    views := nil
+	]
     ].
     topViews notNil ifTrue:[
-        topViews removeIdentical:aView ifAbsent:nil.
-        topViews isEmpty ifTrue:[
-            topViews := nil
-        ]
+	topViews removeIdentical:aView ifAbsent:nil.
+	topViews isEmpty ifTrue:[
+	    topViews := nil
+	]
     ].
     "
      wakeup my process to look if last view has been
      removed (modalBoxes terminate their modalLoop if so)
     "
     mySensor notNil ifTrue:[
-        (sema := mySensor eventSemaphore) notNil ifTrue:[
-            sema signal
-        ]
+	(sema := mySensor eventSemaphore) notNil ifTrue:[
+	    sema signal
+	]
     ]
 
     "Modified: 1.2.1997 / 12:13:26 / cg"
@@ -623,11 +640,11 @@
     "destroy all views associated to this window group"
 
     topViews notNil ifTrue:[
-        topViews do:[:aTopView | 
-            aTopView notNil ifTrue:[
-                aTopView destroy
-            ]
-        ]
+	topViews do:[:aTopView | 
+	    aTopView notNil ifTrue:[
+		aTopView destroy
+	    ]
+	]
     ].
     views := nil.
     topViews := nil.
@@ -654,14 +671,14 @@
      my views."
 
     topViews notNil ifTrue:[
-        "
-         need a new semaphore, since obsolete processes 
-         (from our previous live) may still sit on the current semaphore
-        "
-        mySensor eventSemaphore:(Semaphore new name:'WGroup eventSema').
-        isModal ifFalse:[
-            self startupWith:[self restartTopViews].
-        ]
+	"
+	 need a new semaphore, since obsolete processes 
+	 (from our previous live) may still sit on the current semaphore
+	"
+	mySensor eventSemaphore:(Semaphore new name:'WGroup eventSema').
+	isModal ifFalse:[
+	    self startupWith:[self restartTopViews].
+	]
     ]
 
     "Modified: / 6.5.1999 / 09:46:08 / cg"
@@ -672,12 +689,12 @@
      about the restart."
 
     topViews notNil ifTrue:[
-        topViews do:[:aView |
-            aView isPopUpView ifFalse:[
+	topViews do:[:aView |
+	    aView isPopUpView ifFalse:[
 "/                aView realize.
-                aView restarted
-            ].
-        ].
+		aView restarted
+	    ].
+	].
     ].
 
     "Modified: / 6.5.1999 / 09:42:37 / cg"
@@ -956,172 +973,172 @@
      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].
 
-                (mainGroup notNil or:[mySensor hasEvents not]) ifTrue:[
-                    "/ now, wait for an event to arrive
-                    thisProcess setStateTo:#eventWait if:#active.
-                    waitSema isNil ifTrue:[
-                        "/ oops - how can this happen ....
-                        ^ self.
-                    ].
-                    gotSema := waitSema wait.
-                ] ifFalse:[
-                    gotSema := mySema
-                ].
-                LastActiveGroup := self.
-                LastActiveProcess := thisProcess.
+		(mainGroup notNil or:[mySensor hasEvents not]) ifTrue:[
+		    "/ now, wait for an event to arrive
+		    thisProcess setStateTo:#eventWait if:#active.
+		    waitSema isNil ifTrue:[
+			"/ oops - how can this happen ....
+			^ self.
+		    ].
+		    gotSema := waitSema wait.
+		] ifFalse:[
+		    gotSema := mySema
+		].
+		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"
@@ -1157,51 +1174,51 @@
     self processExposeEvents.
 
     LastEventQuerySignal handle:[:ex |
-        ex proceedWith:event
+	ex proceedWith:event
     ] do:[
-        [mySensor notNil
-         and:[(event := mySensor nextEvent) notNil]] whileTrue:[
-            ignore := false.
-            focus := focusView.
-            modalDelegate := false.
-            modalTop := nil.
+	[mySensor notNil
+	 and:[(event := mySensor nextEvent) notNil]] whileTrue:[
+	    ignore := false.
+	    focus := focusView.
+	    modalDelegate := false.
+	    modalTop := nil.
 
-            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.
-                    ].
-                    modalGroup focusView notNil ifTrue:[
-                        focus := modalGroup focusView
-                    ]
-                ] ifFalse:[
-                    event isFocusEvent ifTrue:[
-                        event isFocusInEvent ifTrue:[
-                            "/ move focus over to modalBox
-                            modalTop notNil ifTrue:[
-                                modalTop getKeyboardFocus.
-                                "/ 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.
+		    ].
+		    modalGroup focusView notNil ifTrue:[
+			focus := modalGroup focusView
+		    ]
+		] ifFalse:[
+		    event isFocusEvent ifTrue:[
+			event isFocusInEvent ifTrue:[
+			    "/ move focus over to modalBox
+			    modalTop notNil ifTrue:[
+				modalTop getKeyboardFocus.
+				"/ 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.
@@ -1211,112 +1228,112 @@
 "/                                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:[
+	    ignore ifFalse:[
+		(views notNil or:[topViews notNil]) ifTrue:[
 
-                    "/ give eventRecorders, catchers etc. 
-                    "/ a chance to eat or modify that event
+		    "/ give eventRecorders, catchers etc. 
+		    "/ a chance to eat or modify that event
 
-                    (preEventHook  notNil 
-                    and:[preEventHook processEvent:event]) ifTrue:[
-                        ignore := true.
-                    ].
+		    (preEventHook  notNil 
+		    and:[preEventHook processEvent:event]) ifTrue:[
+			ignore := true.
+		    ].
 
-                    ignore ifFalse:[
-                        evView := event view.
+		    ignore ifFalse:[
+			evView := event view.
 
-                        (event isKeyEvent 
-                        and:[(keyboardProcessor := (modalTop ? evView topView) keyboardProcessor) notNil]) ifTrue:[
-                            ignore := keyboardProcessor processEvent:event forModalView:modalTop
-                        ].
-                    ].
+			(event isKeyEvent 
+			and:[(keyboardProcessor := (modalTop ? evView topView) keyboardProcessor) notNil]) ifTrue:[
+			    ignore := keyboardProcessor processEvent:event forModalView:modalTop
+			].
+		    ].
 
-                    ignore ifFalse:[
-                        "/ event handling below will vanish ...
-                        "/ (keyboardProcessor will do it)
+		    ignore ifFalse:[
+			"/ event handling below will vanish ...
+			"/ (keyboardProcessor will do it)
 
-                        event isKeyPressEvent ifTrue:[
-                            event 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
-                                ]
-                            ]
-                        ].
+			event isKeyPressEvent ifTrue:[
+			    event 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 reverts
-                        "/ to implicit focus control
-                        "/ This used to be done for every click -
-                        "/ but behaved ugly if clicking in a scrollbar ...
+			"/
+			"/ buttonPress events turn off explicit focus, and reverts
+			"/ to implicit focus control
+			"/ This used to be done for every click -
+			"/ but behaved ugly if clicking in a scrollbar ...
 
-                        event isButtonPressEvent ifTrue:[
-                            (evView wantsFocusWithButtonPress) ifTrue:[
-                                self focusView:evView.
-                            ].
-                        ].
+			event isButtonPressEvent ifTrue:[
+			    (evView wantsFocusWithButtonPress) ifTrue:[
+				self focusView:evView.
+			    ].
+			].
 
-                        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
+			]
+		    ].
 
-                    "/ give eventRecorders, postProcessors 
-                    "/ a chance to see that event
+		    "/ give eventRecorders, postProcessors 
+		    "/ a chance to see that event
 
-                    postEventHook notNil ifTrue:[
-                        postEventHook processEvent:event
-                    ].
-                ]
-            ].
-        ]
+		    postEventHook notNil ifTrue:[
+			postEventHook processEvent:event
+		    ].
+		]
+	    ].
+	]
     ]
 
     "Created: / 5.3.1997 / 11:33:11 / cg"
@@ -1338,44 +1355,44 @@
 
     (sensor := mySensor) isNil ifTrue:[^ self].
     (sensor damageCount ~~ 0) ifTrue:[
-        thisProcess := Processor activeProcess.
+	thisProcess := Processor activeProcess.
 
-        [(event := sensor nextDamageEventFor:aViewOrNil) notNil] whileTrue:[
-            LastActiveGroup := self.
-            LastActiveProcess := thisProcess.
+	[(event := sensor nextDamageEventFor:aViewOrNil) notNil] whileTrue:[
+	    LastActiveGroup := self.
+	    LastActiveProcess := thisProcess.
 
-            (views notNil or:[topViews notNil]) ifTrue:[
-                view := event view.
-                (aViewOrNil isNil or:[aViewOrNil == view]) ifTrue:[
-                    LastEventQuerySignal handle:[:ex |
-                        ex proceedWith:event
-                    ] do:[
-                        (preEventHook notNil 
-                        and:[preEventHook processEvent:event]) ifFalse:[
-                            "/
-                            "/ if the view is no longer shown (iconified or closed),
-                            "/ this is a leftover event and ignored.
-                            "/
-                            "/ could this ever be a non-damage ?
-                            "/
-                            (view shown or:[event isDamage not]) ifTrue:[
-                                LastActiveGroup := self.
-                                LastActiveProcess := thisProcess.
+	    (views notNil or:[topViews notNil]) ifTrue:[
+		view := event view.
+		(aViewOrNil isNil or:[aViewOrNil == view]) ifTrue:[
+		    LastEventQuerySignal handle:[:ex |
+			ex proceedWith:event
+		    ] do:[
+			(preEventHook notNil 
+			and:[preEventHook processEvent:event]) ifFalse:[
+			    "/
+			    "/ if the view is no longer shown (iconified or closed),
+			    "/ this is a leftover event and ignored.
+			    "/
+			    "/ could this ever be a non-damage ?
+			    "/
+			    (view shown or:[event isDamage not]) ifTrue:[
+				LastActiveGroup := self.
+				LastActiveProcess := thisProcess.
 
-                                view
-                                    dispatchEvent:(event type) 
-                                    arguments:(event arguments) 
-                                    withFocusOn:nil 
-                                    delegate:true
-                            ].
-                        ]
-                    ].
-                    postEventHook notNil ifTrue:[
-                        postEventHook processEvent:event
-                    ]
-                ]
-            ]
-        ]
+				view
+				    dispatchEvent:(event type) 
+				    arguments:(event arguments) 
+				    withFocusOn:nil 
+				    delegate:true
+			    ].
+			]
+		    ].
+		    postEventHook notNil ifTrue:[
+			postEventHook processEvent:event
+		    ]
+		]
+	    ]
+	]
     ]
 
     "Created: / 3.12.1998 / 14:01:39 / cg"
@@ -1499,33 +1516,33 @@
 
     sequence := self focusSequence.
     (lastIndex := sequence size) == 0 ifTrue:[
-        ^ self
+	^ self
     ].
 
     focusView isNil ifTrue:[
-        index := 0
+	index := 0
     ] ifFalse:[
-        index := index0 := self indexOfFocusViewInFocusSequence.
+	index := index0 := self indexOfFocusViewInFocusSequence.
     ].
 
     [next isNil] whileTrue:[
-        index := index + 1.
-        index > lastIndex ifTrue:[
-            index := 1.
-            index0 isNil ifTrue:[^ self ].
-        ].
-        index == index0 ifTrue:[
-            ^ self
-        ].
+	index := index + 1.
+	index > lastIndex ifTrue:[
+	    index := 1.
+	    index0 isNil ifTrue:[^ self ].
+	].
+	index == index0 ifTrue:[
+	    ^ self
+	].
 
-        next := (sequence at:index).
-        next realized not ifTrue:[
-            next := nil
-        ] ifFalse:[
-            next enabled ifFalse:[
-                next := nil
-            ]
-        ]
+	next := (sequence at:index).
+	next realized not ifTrue:[
+	    next := nil
+	] ifFalse:[
+	    next enabled ifFalse:[
+		next := nil
+	    ]
+	]
     ].
 
     self focusView:next byTab:true
@@ -1566,31 +1583,31 @@
     (lastIndex := sequence size) == 0 ifTrue:[^ self].
 
     focusView isNil ifTrue:[
-        index := 0
+	index := 0
     ] ifFalse:[
-        index := self indexOfFocusViewInFocusSequence.
-        index0 := index.
+	index := self indexOfFocusViewInFocusSequence.
+	index0 := index.
     ].
     index == 0 ifTrue:[
-        index := lastIndex + 1.
+	index := lastIndex + 1.
     ].
 
     [prev isNil] whileTrue:[
-        index := index - 1.
-        index < 1 ifTrue:[
-            index := lastIndex.
-            index0 isNil ifTrue:[^ self].
-        ].
-        index == index0 ifTrue:[^ self].
+	index := index - 1.
+	index < 1 ifTrue:[
+	    index := lastIndex.
+	    index0 isNil ifTrue:[^ self].
+	].
+	index == index0 ifTrue:[^ self].
 
-        prev := (sequence at:index).
-        prev realized not ifTrue:[
-            prev := nil
-        ] ifFalse:[
-            prev enabled ifFalse:[
-                prev := nil
-            ]
-        ].
+	prev := (sequence at:index).
+	prev realized not ifTrue:[
+	    prev := nil
+	] ifFalse:[
+	    prev enabled ifFalse:[
+		prev := nil
+	    ]
+	].
     ].
 
     self focusView:prev byTab:true
@@ -1618,27 +1635,23 @@
     myDisplay := self graphicsDevice.
     (myDisplay notNil 
     and:[myDisplay activateOnClick:nil]) ifTrue:[
-        i := FocusViewPerDisplay at:myDisplay ifAbsent:nil.
-        i notNil ifTrue:[
-            prevFocusView := i key.
-        ].
-
-        (prevFocusView notNil 
-        and:[prevFocusView windowGroup ~~ aView windowGroup]) ifTrue:[
-            "/ a view from another windowGroup requests the focus.
-            "/ Do not grant this, if in windows-activateOnClick mode.
+	prevFocusView := myDisplay focusView.
+	(prevFocusView notNil 
+	and:[prevFocusView windowGroup ~~ aView windowGroup]) ifTrue:[
+	    "/ a view from another windowGroup requests the focus.
+	    "/ Do not grant this, if in windows-activateOnClick mode.
 
 "/            ' not granted' printCR.
-            myDisplay setInputFocusTo:prevFocusView.
-            ^ false
-        ].
+	    myDisplay setInputFocusTo:prevFocusView.
+	    ^ false
+	].
     ].
 
 "/    ' granted' printCR.
 
     (focusView isNil or:[focusByTab not]) ifTrue:[
-        self focusView:aView byTab:false.
-        ^ true
+	self focusView:aView byTab:false.
+	^ true
     ].
     ^ false
 
@@ -1685,18 +1698,18 @@
     |seq doAssignFocusView|
 
     focusView == aViewOrNil ifFalse:[
-        doAssignFocusView := false.
-        topViews isNil ifTrue:[
-            "/ mhmh - a topview-less windowGroup
-            doAssignFocusView := true.
-        ] ifFalse:[
-            (seq := self focusSequence) notNil ifTrue:[
-                doAssignFocusView := (seq includesIdentical:aViewOrNil).
-            ]
-        ].
-        doAssignFocusView ifTrue:[
-            self focusView:aViewOrNil.
-        ]
+	doAssignFocusView := false.
+	topViews isNil ifTrue:[
+	    "/ mhmh - a topview-less windowGroup
+	    doAssignFocusView := true.
+	] ifFalse:[
+	    (seq := self focusSequence) notNil ifTrue:[
+		doAssignFocusView := (seq includesIdentical:aViewOrNil).
+	    ]
+	].
+	doAssignFocusView ifTrue:[
+	    self focusView:aViewOrNil.
+	]
     ]
 
     "Created: / 18.9.1998 / 16:28:27 / cg"
@@ -1733,57 +1746,50 @@
      If it came via tabbing, the view is notified differently, to allow
      for special highlighting (i.e. drawing a focus-border around itself)"
 
-    |i prevFocusView prevFocusCameViaTab myDisplay|
+    |i prevFocusView myDisplay|
 
 "/  'focusToView:' print. aViewOrNil printCR. 
 
     myDisplay := self graphicsDevice.
     myDisplay notNil ifTrue:[
-        "/
-        "/ take the focus from whichEver view had it previously
-        "/
-        i := FocusViewPerDisplay at:myDisplay ifAbsent:nil.
-        i notNil ifTrue:[
-            prevFocusView := i key.
-            prevFocusCameViaTab := i value
-        ].
-
-        (prevFocusView notNil 
-        and:[prevFocusView ~~ aViewOrNil]) ifTrue:[
-            prevFocusView showNoFocus:prevFocusCameViaTab. "/ true is bad - see pullDownMenu.
-            prevFocusView hasKeyboardFocus:false.
-        ].
-        FocusViewPerDisplay at:myDisplay put:(aViewOrNil->focusCameViaTab).
+	"/
+	"/ take the focus from whichEver view had it previously
+	"/
+	prevFocusView := myDisplay focusView.
+	prevFocusView ~~ aViewOrNil ifTrue:[
+	    self class takeFocusFromDevice:myDisplay.
+	].
+	myDisplay focusView:aViewOrNil.
     ].
 
     focusView == aViewOrNil ifTrue:[
-        focusView notNil ifTrue:[
-            "/ this is the case when the mouse-pointer reenters
-            "/ into a topView which had a focusView
-            focusByTab := focusCameViaTab or:[focusByTab].
-            focusView showFocus:focusByTab.
-            aViewOrNil hasKeyboardFocus:true.
-            FocusViewPerDisplay at:myDisplay put:(aViewOrNil->focusByTab).
-        ].
-        ^ self
+	focusView notNil ifTrue:[
+	    "/ this is the case when the mouse-pointer reenters
+	    "/ into a topView which had a focusView
+	    focusByTab := focusCameViaTab or:[focusByTab].
+	    focusView showFocus:focusByTab.
+	    aViewOrNil hasKeyboardFocus:true.
+	    myDisplay focusView:aViewOrNil.
+	].
+	^ self
     ].
 
     focusView notNil ifTrue:[
-        "/ lost explicit focus
-        focusView == aViewOrNil ifTrue:[
-            aViewOrNil hasKeyboardFocus:true.
-            FocusViewPerDisplay at:myDisplay put:(aViewOrNil->focusCameViaTab).
-            ^ self
-        ].
+	"/ lost explicit focus
+	focusView == aViewOrNil ifTrue:[
+	    aViewOrNil hasKeyboardFocus:true.
+	    myDisplay focusView:aViewOrNil.
+	    ^ self
+	].
     ].
 
     focusView := aViewOrNil.
     focusView notNil ifTrue:[
-        "/ got explicit focus
-        aViewOrNil showFocus:focusCameViaTab.
-        aViewOrNil hasKeyboardFocus:true.
-        focusByTab := focusCameViaTab.
-        FocusViewPerDisplay at:myDisplay put:(aViewOrNil->focusCameViaTab).
+	"/ got explicit focus
+	aViewOrNil showFocus:focusCameViaTab.
+	aViewOrNil hasKeyboardFocus:true.
+	focusByTab := focusCameViaTab.
+	myDisplay focusView:aViewOrNil.
     ].
 
     "
@@ -1808,20 +1814,20 @@
     sequence := self focusSequence.
 
     focusView notNil ifTrue:[
-        index := (sequence identityIndexOf:focusView).
-        index == 0 ifTrue:[
-            "/ mhmh - how comes ?
-            "/ (in rare cases, a subwidget of one of my 
-            "/  focusSequence-widgets has the focus.
-            "/  in that case, care for this here)
-            v := focusView superView.
-            [index == 0 and:[v notNil]] whileTrue:[
-                index := (sequence identityIndexOf:v).
-                v := v superView
-            ].
-        ]
+	index := (sequence identityIndexOf:focusView).
+	index == 0 ifTrue:[
+	    "/ mhmh - how comes ?
+	    "/ (in rare cases, a subwidget of one of my 
+	    "/  focusSequence-widgets has the focus.
+	    "/  in that case, care for this here)
+	    v := focusView superView.
+	    [index == 0 and:[v notNil]] whileTrue:[
+		index := (sequence identityIndexOf:v).
+		v := v superView
+	    ].
+	]
     ] ifFalse:[
-        index := 0.
+	index := 0.
     ].
     ^ index
 ! !
@@ -2068,6 +2074,6 @@
 !WindowGroup class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/WindowGroup.st,v 1.174 1999-05-20 16:35:21 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/WindowGroup.st,v 1.175 1999-05-23 12:48:40 cg Exp $'
 ! !
 WindowGroup initialize!