TopView.st
changeset 5614 7c75195a84c1
parent 5287 b25ac0bdfbe7
child 5620 4dd0cdcf76a3
--- a/TopView.st	Mon Oct 11 11:06:42 2010 +0200
+++ b/TopView.st	Mon Oct 11 11:06:49 2010 +0200
@@ -1,6 +1,6 @@
 "
  COPYRIGHT (c) 1995 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -27,7 +27,7 @@
 copyright
 "
  COPYRIGHT (c) 1995 by Claus Gittinger
-              All Rights Reserved
+	      All Rights Reserved
 
  This software is furnished under a license and may be used
  only in accordance with the terms of that license and with the
@@ -47,21 +47,21 @@
     topViews are typically instances of StandardSystemView.
 
     [instance variables:]
-        type            <Integer>       encodes master/slave relationship:
-                                            #normal, #master, #slave or #partner
-                                        for modeless views
-                                        (the #master-, #slave- or #partner-type links multiple views 
-                                         into a windowManagers windowGroup -> for de-iconification)
+	type            <Integer>       encodes master/slave relationship:
+					    #normal, #master, #slave or #partner
+					for modeless views
+					(the #master-, #slave- or #partner-type links multiple views
+					 into a windowManagers windowGroup -> for de-iconification)
 
-                                        encodes window type:
-                                            #normal, #dialog, #popup, #undecorated 
+					encodes window type:
+					    #normal, #dialog, #popup, #undecorated
 
     [see also:]
-        StandardSystemView PopUpView DialogBox 
-        ( introduction to view programming :html: programming/viewintro.html )
+	StandardSystemView PopUpView DialogBox
+	( introduction to view programming :html: programming/viewintro.html )
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 !
 
@@ -75,108 +75,108 @@
 
   Modeless:
     regular style:
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v extent:200@200.
-        v open
-                                                            [exEnd]
+	v := TopView new.
+	v extent:200@200.
+	v open
+							    [exEnd]
 
     dialog:
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v beDialogView.
-        v extent:200@200.
-        v open
-        Delay waitForSeconds:10. v destroy.
-                                                            [exEnd]
+	v := TopView new.
+	v beDialogView.
+	v extent:200@200.
+	v open
+	Delay waitForSeconds:10. v destroy.
+							    [exEnd]
 
     popUp (always on top):
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v bePopUpView.
-        v extent:200@200.
-        v open.
-        Delay waitForSeconds:10. v destroy.
-                                                            [exEnd]
+	v := TopView new.
+	v bePopUpView.
+	v extent:200@200.
+	v open.
+	Delay waitForSeconds:10. v destroy.
+							    [exEnd]
 
     undecorated (looks loke popUp, but is not always on top):
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v beUndecorated.
-        v extent:200@200.
-        v open.
-        Delay waitForSeconds:10. v destroy.
-                                                            [exEnd]
+	v := TopView new.
+	v beUndecorated.
+	v extent:200@200.
+	v open.
+	Delay waitForSeconds:10. v destroy.
+							    [exEnd]
 
     toolwindow (looks loke normal, but has smaller windowTitle-area on win32):
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v beToolWindow.
-        v extent:200@200.
-        v open.
-        Delay waitForSeconds:10. v destroy.
-                                                            [exEnd]
+	v := TopView new.
+	v beToolWindow.
+	v extent:200@200.
+	v open.
+	Delay waitForSeconds:10. v destroy.
+							    [exEnd]
 
     toolwindow dialog (looks loke normal, but has smaller windowTitle-area on win32):
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v beToolDialog.
-        v extent:200@200.
-        v open.
-        Delay waitForSeconds:10. v destroy.
-                                                            [exEnd]
+	v := TopView new.
+	v beToolDialog.
+	v extent:200@200.
+	v open.
+	Delay waitForSeconds:10. v destroy.
+							    [exEnd]
 
   Modal:
     regular style:
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v extent:200@200.
-        v openModal
-                                                            [exEnd]
+	v := TopView new.
+	v extent:200@200.
+	v openModal
+							    [exEnd]
 
     dialog:
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v beDialogView.
-        v extent:200@200.
-        v openModal
-                                                            [exEnd]
+	v := TopView new.
+	v beDialogView.
+	v extent:200@200.
+	v openModal
+							    [exEnd]
 
     popUp (always on top):
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v bePopUpView.
-        v extent:200@200.
-        v openModal
-                                                            [exEnd]
+	v := TopView new.
+	v bePopUpView.
+	v extent:200@200.
+	v openModal
+							    [exEnd]
 
     undecorated (looks loke popUp, but is not always on top):
-                                                            [exBegin]
-        |v|
+							    [exBegin]
+	|v|
 
-        v := TopView new.
-        v beUndecorated.
-        v extent:200@200.
-        v openModal
-                                                            [exEnd]
+	v := TopView new.
+	v beUndecorated.
+	v extent:200@200.
+	v openModal
+							    [exEnd]
 
 "
 ! !
@@ -215,13 +215,13 @@
 
     display := Screen current.
     display isNil ifTrue:[
-        ^ 600 @ 400
+	^ 600 @ 400
     ].
     ^ display defaultExtentForTopViews
 !
 
 forceModalBoxesToOpenAtCenter
-    "return the flag which forces all modal views to be opened 
+    "return the flag which forces all modal views to be opened
      at the screens center"
 
     ^ ForceModalBoxesToOpenAtCenter ? false
@@ -240,14 +240,14 @@
 !
 
 forceModalBoxesToOpenAtPointer
-    "return the flag which forces all modal views to be opened 
+    "return the flag which forces all modal views to be opened
      at the current pointer position"
 
     ^ ForceModalBoxesToOpenAtPointer ? false
 !
 
 forceModalBoxesToOpenAtPointer:aBoolean
-    "set/clear the flag which forces all modal views to be opened 
+    "set/clear the flag which forces all modal views to be opened
      at the current pointer position"
 
     ForceModalBoxesToOpenAtPointer := aBoolean
@@ -310,10 +310,10 @@
 
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:WindowTypeMask) bitOr:TypeDialog.
-        ^ self.
+	type := (type bitClear:WindowTypeMask) bitOr:TypeDialog.
+	^ self.
     ].
-    type := #dialog 
+    type := #dialog
 !
 
 beIndependent
@@ -323,8 +323,8 @@
 
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := type bitClear:MasterSlaveMask.
-        ^ self.
+	type := type bitClear:MasterSlaveMask.
+	^ self.
     ].
     type := nil
 !
@@ -334,15 +334,15 @@
 !
 
 beMaster
-    "make this a master-view. 
+    "make this a master-view.
      All slave views within the same windowGroup will be closed if any master is closed
      and also de/iconify together with their master(s).
      (i.e. they follow their master(s))."
 
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:MasterSlaveMask) bitOr:TypeMaster.
-        ^ self.
+	type := (type bitClear:MasterSlaveMask) bitOr:TypeMaster.
+	^ self.
     ].
     type := #master
 
@@ -354,15 +354,15 @@
 !
 
 bePartner
-    "make this a partner-view. Each partner-view will automatically 
+    "make this a partner-view. Each partner-view will automatically
      close other partner views (within the same windowGroup) when closed."
 
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:MasterSlaveMask) bitOr:TypePartner.
-        ^ self.
+	type := (type bitClear:MasterSlaveMask) bitOr:TypePartner.
+	^ self.
     ].
-    type := #partner 
+    type := #partner
 
     "
      create two topViews within the same group:
@@ -386,10 +386,10 @@
 bePopUpView
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:WindowTypeMask) bitOr:TypePopUp.
-        ^ self.
+	type := (type bitClear:WindowTypeMask) bitOr:TypePopUp.
+	^ self.
     ].
-    type := #popup 
+    type := #popup
 !
 
 beScreenDialog
@@ -398,10 +398,10 @@
 
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:WindowTypeMask) bitOr:TypeScreenDialog.
-        ^ self.
+	type := (type bitClear:WindowTypeMask) bitOr:TypeScreenDialog.
+	^ self.
     ].
-    type := #dialog 
+    type := #dialog
 !
 
 beSlave
@@ -411,10 +411,10 @@
 
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:MasterSlaveMask) bitOr:TypeSlave.
-        ^ self.
+	type := (type bitClear:MasterSlaveMask) bitOr:TypeSlave.
+	^ self.
     ].
-    type := #slave 
+    type := #slave
 
     "
      create two topViews within the same group:
@@ -439,19 +439,19 @@
 beToolDialog
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:WindowTypeMask) bitOr:TypeToolDialog.
-        ^ self.
+	type := (type bitClear:WindowTypeMask) bitOr:TypeToolDialog.
+	^ self.
     ].
-    type := #dialog 
+    type := #dialog
 !
 
 beToolWindow
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:WindowTypeMask) bitOr:TypeToolWindow.
-        ^ self.
+	type := (type bitClear:WindowTypeMask) bitOr:TypeToolWindow.
+	^ self.
     ].
-    type := nil 
+    type := nil
 !
 
 beUndecorated
@@ -459,8 +459,8 @@
 
     "/ the nonInteger handling code is for backward compatibility only.
     type isInteger ifTrue:[
-        type := (type bitClear:WindowTypeMask) bitOr:TypeUndecorated.
-        ^ self.
+	type := (type bitClear:WindowTypeMask) bitOr:TypeUndecorated.
+	^ self.
     ].
     type := nil
 !
@@ -494,9 +494,9 @@
      may then receive tray*-events in the future."
 
     self device
-         addTrayIconFor:self
-         icon:anImageOrForm iconMask:nil
-         toolTipMessage:toolTipMessage
+	 addTrayIconFor:self
+	 icon:anImageOrForm iconMask:nil
+	 toolTipMessage:toolTipMessage
 
     "
      |v icon|
@@ -514,30 +514,30 @@
 !TopView methodsFor:'event handling'!
 
 keyPress:key x:x y:y
-    "notice: this ought to be moved into the upcoming 
+    "notice: this ought to be moved into the upcoming
      StandardSystemViewController."
 
-    <resource: #keyboard ( #Tab 
-                           #FocusNext #FocusPrevious 
-                           #CursorDown #CursorUp ) >
+    <resource: #keyboard ( #Tab
+			   #FocusNext #FocusPrevious
+			   #CursorDown #CursorUp ) >
 
     windowGroup notNil ifTrue:[
-        key == #Tab ifTrue:[
-            self sensor shiftDown ifTrue:[
-                windowGroup focusPrevious
-            ] ifFalse:[
-                windowGroup focusNext
-            ].
-            ^ self.
-        ].
-        (key == #FocusNext or:[key == #CursorDown]) ifTrue:[
-            windowGroup focusNext.
-            ^ self.
-        ].
-        (key == #FocusPrevious or:[key == #CursorUp])  ifTrue:[
-            windowGroup focusPrevious.
-            ^ self.
-        ].
+	key == #Tab ifTrue:[
+	    self sensor shiftDown ifTrue:[
+		windowGroup focusPrevious
+	    ] ifFalse:[
+		windowGroup focusNext
+	    ].
+	    ^ self.
+	].
+	(key == #FocusNext or:[key == #CursorDown]) ifTrue:[
+	    windowGroup focusNext.
+	    ^ self.
+	].
+	(key == #FocusPrevious or:[key == #CursorUp])  ifTrue:[
+	    windowGroup focusPrevious.
+	    ^ self.
+	].
     ].
 
     super keyPress:key x:x y:y
@@ -547,7 +547,7 @@
 !
 
 showActivity:someMessage
-    "some activityNotification shalt be communicated to the user. 
+    "some activityNotification shalt be communicated to the user.
      Default for activity notifications here: ignore them"
 
     ^ self
@@ -646,16 +646,16 @@
 "/        componentWithInitialFocus := keyboardProcessor componentWithInitialFocus.
 "/        componentWithInitialFocus notNil ifTrue:[
 "/            self windowGroup focusView:componentWithInitialFocus byTab:true.
-"/            "/ componentWithInitialFocus requestFocus.                    
+"/            "/ componentWithInitialFocus requestFocus.
 "/            ^ self.
 "/        ]
 "/    ].
 
-    (windowGroup notNil 
+    (windowGroup notNil
     and:[(componentWithInitialFocus := windowGroup defaultKeyboardConsumer) notNil]) ifTrue:[
-        windowGroup focusView:componentWithInitialFocus byTab:true "false".
+	windowGroup focusView:componentWithInitialFocus byTab:true "false".
     ] ifFalse:[
-        self assignKeyboardFocusToFirstInputField.
+	self assignKeyboardFocusToFirstInputField.
     ].
 !
 
@@ -667,28 +667,28 @@
     |firstInputField firstConsumer firstCursorConsumer consumer|
 
     self allSubViewsDo:[:v |
-        (firstInputField isNil and:[v isInputField]) ifTrue:[
-            firstInputField := v
-        ].
-        (firstConsumer isNil and:[v isKeyboardConsumer]) ifTrue:[
-            firstConsumer := v
-        ].
-        (firstCursorConsumer isNil and:[v isCursorKeyConsumer]) ifTrue:[
-            firstCursorConsumer := v
-        ].
+	(firstInputField isNil and:[v isInputField]) ifTrue:[
+	    firstInputField := v
+	].
+	(firstConsumer isNil and:[v isKeyboardConsumer]) ifTrue:[
+	    firstConsumer := v
+	].
+	(firstCursorConsumer isNil and:[v isCursorKeyConsumer]) ifTrue:[
+	    firstCursorConsumer := v
+	].
     ].
     self preferFirstInputFieldWhenAssigningInitialFocus ifTrue:[
-        consumer := firstInputField.
+	consumer := firstInputField.
     ].
     consumer := (consumer ? firstConsumer ? firstCursorConsumer).
     consumer notNil ifTrue:[
-        device platformName = 'WIN32' ifTrue:[
-            self windowGroup focusView:consumer byTab:true.
-        ] ifFalse:[
-            consumer requestFocus.
-            "/ consumer requestFocus. - could be denied; but we force it here
-            windowGroup focusView:consumer byTab:false.
-        ].
+	device platformName = 'WIN32' ifTrue:[
+	    self windowGroup focusView:consumer byTab:true.
+	] ifFalse:[
+	    consumer requestFocus.
+	    "/ consumer requestFocus. - could be denied; but we force it here
+	    windowGroup focusView:consumer byTab:false.
+	].
     ].
 
     "Modified: / 29-08-2006 / 14:32:30 / cg"
@@ -718,13 +718,16 @@
 initialize
     "initialize the topViews position for the screens center"
 
-    |screenCenter|
+    |screenBounds screenCenter|
 
     super initialize.
 
     device initializeTopViewHookFor:self.
 
-    screenCenter := device center.
+"/ ****** MULTI SCREEN
+    screenBounds := device monitorBoundsAt:(device pointerPosition).
+    screenCenter := screenBounds center rounded.
+
     left := screenCenter x - (width // 2).
     top := screenCenter y - (height // 2).
     type := 0
@@ -734,7 +737,7 @@
     super postRealize.
 
     keyboardProcessor isNil ifTrue:[
-        keyboardProcessor := KeyboardProcessor new.
+	keyboardProcessor := KeyboardProcessor new.
     ].
 
     device realizedTopViewHookFor:self
@@ -742,18 +745,18 @@
 
 realize
     self isMarkedAsUnmappedModalBox ifTrue:[
-        "/ must clear this flag
-        "/ - otherwise realize thinks it is already realized.
-        realized := false.
-        self unmarkAsUnmappedModalBox.
+	"/ must clear this flag
+	"/ - otherwise realize thinks it is already realized.
+	realized := false.
+	self unmarkAsUnmappedModalBox.
     ].
     super realize.
 !
 
 release
     keyboardProcessor notNil ifTrue:[
-        keyboardProcessor release.
-        keyboardProcessor := nil.
+	keyboardProcessor release.
+	keyboardProcessor := nil.
     ].
     super release
 ! !
@@ -765,7 +768,7 @@
 
     self isCollapsed ifTrue:[
 "/        self unmap.
-        self realize.
+	self realize.
     ].
     self raise
 
@@ -783,7 +786,7 @@
      when invoking commands with the rDoit mechanism"
 
     [drawableId isNil] whileFalse:[
-        Delay waitForSeconds:0.1.
+	Delay waitForSeconds:0.1.
     ].
 
     "asynchronous:
@@ -804,7 +807,7 @@
      Return the value as returned by aBlock."
 
     windowGroup notNil ifTrue:[
-        ^ windowGroup withCursor:aCursor do:aBlock
+	^ windowGroup withCursor:aCursor do:aBlock
     ].
     ^ super withCursor:aCursor do:aBlock
 ! !
@@ -827,7 +830,7 @@
      With click-to-focus behavior, this is obviously the current application.
      Use this query with caution, for example, to suppress tooltips for inactive apps."
 
-    ^ windowGroup notNil and:[windowGroup anyViewHasFocus] 
+    ^ windowGroup notNil and:[windowGroup anyViewHasFocus]
 !
 
 isCollapsed
@@ -843,7 +846,7 @@
     "return true if this is a dialog view"
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:WindowTypeMask) == TypeDialog
+	^ (type bitAnd:WindowTypeMask) == TypeDialog
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ type == #dialog
@@ -857,7 +860,7 @@
     "return true, if this is a masterView"
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:MasterSlaveMask) == TypeMaster
+	^ (type bitAnd:MasterSlaveMask) == TypeMaster
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ type == #master
@@ -874,7 +877,7 @@
     "return true, if this is a partnerView"
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:MasterSlaveMask) == TypePartner
+	^ (type bitAnd:MasterSlaveMask) == TypePartner
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ type == #partner
@@ -885,7 +888,7 @@
      (i.e. I want to come up without decoration and popUp to top immediately)"
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:WindowTypeMask) == TypePopUp
+	^ (type bitAnd:WindowTypeMask) == TypePopUp
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ type == #popup
@@ -899,7 +902,7 @@
      (i.e. I want to come up anove all other windows"
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:WindowTypeMask) == TypeScreenDialog
+	^ (type bitAnd:WindowTypeMask) == TypeScreenDialog
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ false
@@ -909,7 +912,7 @@
     "return true, if this is a slaveView"
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:MasterSlaveMask) == TypeSlave
+	^ (type bitAnd:MasterSlaveMask) == TypeSlave
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ type == #slave
@@ -920,7 +923,7 @@
      (i.e. I want to come up with a smaller window-title area)"
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:WindowTypeMask) == TypeToolDialog
+	^ (type bitAnd:WindowTypeMask) == TypeToolDialog
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ false
@@ -931,7 +934,7 @@
      (i.e. I want to come up with a smaller window-title area)"
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:WindowTypeMask) == TypeToolWindow
+	^ (type bitAnd:WindowTypeMask) == TypeToolWindow
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ false
@@ -949,7 +952,7 @@
     "return true if I am an undecorated view."
 
     type isInteger ifTrue:[
-        ^ (type bitAnd:WindowTypeMask) == TypeUndecorated
+	^ (type bitAnd:WindowTypeMask) == TypeUndecorated
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ false
@@ -963,12 +966,12 @@
 
     "/ If I have an explicit preferredExtent..
     explicitExtent notNil ifTrue:[
-        ^ explicitExtent
+	^ explicitExtent
     ].
 
     "/ If I have a cached preferredExtent value..
     preferredExtent notNil ifTrue:[
-        ^ preferredExtent
+	^ preferredExtent
     ].
     ^ self class defaultExtent
 
@@ -989,13 +992,13 @@
     |t|
 
     type isInteger ifTrue:[
-        t := type bitAnd:WindowTypeMask.
-        t == TypeUndecorated ifTrue:[^ #undecorated].
-        t == TypeDialog ifTrue:[^ #dialog].
-        t == TypePopUp ifTrue:[^ #popUp].
-        t == TypeToolWindow ifTrue:[^ #toolWindow].
-        t == TypeToolDialog ifTrue:[^ #toolDialog].
-        ^ #normal
+	t := type bitAnd:WindowTypeMask.
+	t == TypeUndecorated ifTrue:[^ #undecorated].
+	t == TypeDialog ifTrue:[^ #dialog].
+	t == TypePopUp ifTrue:[^ #popUp].
+	t == TypeToolWindow ifTrue:[^ #toolWindow].
+	t == TypeToolDialog ifTrue:[^ #toolDialog].
+	^ #normal
     ].
     "/ the nonInteger handling code is for backward compatibility only.
     ^ super windowStyle
@@ -1007,7 +1010,7 @@
     "added bell to wake up user"
 
     (self beepWhenOpening) ifTrue:[
-        self beep.
+	self beep.
     ].
     super openModal
 
@@ -1028,7 +1031,7 @@
     "added for MS-windows - much like raise.
      Raise/Activate seem to work only within my own (ST/X)-windows;
      they do not raise one of my views above another (for example: command.com)-window.
-     Can anyone tell me what the difference between raise, activate and setForeground 
+     Can anyone tell me what the difference between raise, activate and setForeground
      really is (I mean really - not what is written in the crappy documentation)"
 
     drawableId isNil ifTrue:[self create].
@@ -1040,7 +1043,7 @@
 !
 
 fixPosition:aPoint
-    "set origin to aPoint, but make sure, that the box is fully visible 
+    "set origin to aPoint, but make sure, that the box is fully visible
      by shifting it into the visible screen area if nescessary.
      This prevents invisible modalBoxes (which you could never close)."
 
@@ -1064,25 +1067,25 @@
 
     (windowGroup notNil
     and:[ windowGroup isModal ]) ifTrue:[
-        masterGroup := windowGroup previousGroup.
-        myApplication := self application.
+	masterGroup := windowGroup previousGroup.
+	myApplication := self application.
 
-        (myApplication notNil 
-        and:[ masterGroup isNil or:[myApplication ~= masterGroup application]]) ifTrue:[
-            AbortOperationRequest handle:[:ex |
-                "/ in case the close is cought by the application
-                ^ self.
-            ] do:[
-                myApplication closeRequest.
+	(myApplication notNil
+	and:[ masterGroup isNil or:[myApplication ~= masterGroup application]]) ifTrue:[
+	    AbortOperationRequest handle:[:ex |
+		"/ in case the close is cought by the application
+		^ self.
+	    ] do:[
+		myApplication closeRequest.
 
-                "/ if myApp called closeDownViews, it wants me to hide.
-                "/ otherwise, it has redefined closeRequest to return without closeDownViews.
-                realized ifTrue:[
-                    "/ closeDownViews was not called - app wants me to remain open
-                    ^ self
-                ].
-            ].
-        ].
+		"/ if myApp called closeDownViews, it wants me to hide.
+		"/ otherwise, it has redefined closeRequest to return without closeDownViews.
+		realized ifTrue:[
+		    "/ closeDownViews was not called - app wants me to remain open
+		    ^ self
+		].
+	    ].
+	].
     ].
     super hide.
 !
@@ -1092,8 +1095,8 @@
      For topViews, the windowManager will choose (or ask for) the
      views position on the screen.
      Notice:
-        Actually, this method is only valid for topViews;
-        however, it is defined here to allow things like 'Button new realize'"
+	Actually, this method is only valid for topViews;
+	however, it is defined here to allow things like 'Button new realize'"
 
     self mapAt:(self origin) iconified:false
 !
@@ -1103,14 +1106,14 @@
      In contrast to map, which does it non-iconified"
 
     realized ifFalse:[
-        "
-         now, make the view visible
-        "
-        realized := true.
-        device
-            mapView:self id:drawableId iconified:true
-            atX:left y:top width:width height:height
-            minExtent:(self minExtent) maxExtent:(self maxExtent)
+	"
+	 now, make the view visible
+	"
+	realized := true.
+	device
+	    mapView:self id:drawableId iconified:true
+	    atX:left y:top width:width height:height
+	    minExtent:(self minExtent) maxExtent:(self maxExtent)
     ]
 
     "Modified: 25.2.1997 / 22:44:33 / cg"
@@ -1135,7 +1138,7 @@
      a different process is currently active - in this case the title bar/icon is flashed.
      this also raises the priority of the sending thread slightly.
 
-     Mark a TopView as #beScreenDialog, to send this on open."                  
+     Mark a TopView as #beScreenDialog, to send this on open."
 
     drawableId isNil ifTrue:[self create].
     device setForegroundWindow:drawableId
@@ -1163,10 +1166,10 @@
 
     drawableId isNil ifTrue:[self create].
     anotherView isNil ifTrue:[
-        otherId := drawableId.
+	otherId := drawableId.
     ] ifFalse:[
-        anotherView create.
-        otherId := anotherView id.
+	anotherView create.
+	otherId := anotherView id.
     ].
     device setTransient:drawableId for:otherId.
     self origin:aPosition.
@@ -1216,14 +1219,14 @@
 !
 
 openIn:aBoundaryRectangle
-    "set origin & extent and open. 
+    "set origin & extent and open.
      The given extent overrides the receivers preferredExtent.
      Added for ST-80 compatibility"
 
-    self 
-        origin:aBoundaryRectangle origin; 
-        extent:aBoundaryRectangle extent; 
-        sizeFixed:true.
+    self
+	origin:aBoundaryRectangle origin;
+	extent:aBoundaryRectangle extent;
+	sizeFixed:true.
     self open
 
     "Modified: 12.2.1997 / 11:58:21 / cg"
@@ -1260,7 +1263,7 @@
 !
 
 openWithExtent:anExtent
-    "set extent and open. The given extent overrides the 
+    "set extent and open. The given extent overrides the
      receivers preferredExtent.
      Added for ST-80 compatibility"
 
@@ -1280,11 +1283,11 @@
 
 !TopView methodsFor:'window events'!
 
-mapped 
+mapped
     "the recevier was mapped (i.e. deiconified);
      look for partners and slaves."
 
-    realized := true. 
+    realized := true.
     super mapped.
 
     "/
@@ -1293,31 +1296,31 @@
     self masterSlaveMessage:#remap inGroup:windowGroup.
 
     self isModal ifTrue:[
-        "take it away from any popup menu possibly still active"
+	"take it away from any popup menu possibly still active"
 
-        self forceUngrabKeyboard.
-        self forceUngrabPointer.
-        "
-         get the focus
-        "
-        self getKeyboardFocus.
-        self enableEnterLeaveEvents
+	self forceUngrabKeyboard.
+	self forceUngrabPointer.
+	"
+	 get the focus
+	"
+	self getKeyboardFocus.
+	self enableEnterLeaveEvents
     ] ifFalse:[
-        "
-         ask for the focus - this avoids having to click on the
-         view with WM's which need an explicit click.
-         Q: is this a good idea ?
-        "
-        TakeFocusWhenMapped == true ifTrue:[
-            self getKeyboardFocus.
-        ]
+	"
+	 ask for the focus - this avoids having to click on the
+	 view with WM's which need an explicit click.
+	 Q: is this a good idea ?
+	"
+	TakeFocusWhenMapped == true ifTrue:[
+	    self getKeyboardFocus.
+	]
     ].
     device platformName = 'WIN32' ifTrue:[
-        self raise
+	self raise
     ].
     self isScreenDialog ifTrue:[
-        self setForegroundWindow.
-        self activate.
+	self setForegroundWindow.
+	self activate.
     ].
 
     "Modified: / 10.9.1998 / 22:02:52 / cg"
@@ -1329,35 +1332,35 @@
      This is a private helper for destroy / mapped / unmapped"
 
     aWindowGroup notNil ifTrue:[
-        "/
-        "/ if I am a master or partner, send to all slaves
-        "/
-        (self isMaster or:[self isPartner]) ifTrue:[
-            aWindowGroup slavesDo:[:v | v perform:aSelector].
-        ].
-        "/
-        "/ if I am a partner, send to all partners
-        "/
-        self isPartner ifTrue:[
-            aWindowGroup partnersDo:[:v | v ~~ self ifTrue:[v perform:aSelector]].
-        ].
+	"/
+	"/ if I am a master or partner, send to all slaves
+	"/
+	(self isMaster or:[self isPartner]) ifTrue:[
+	    aWindowGroup slavesDo:[:v | v perform:aSelector].
+	].
+	"/
+	"/ if I am a partner, send to all partners
+	"/
+	self isPartner ifTrue:[
+	    aWindowGroup partnersDo:[:v | v ~~ self ifTrue:[v perform:aSelector]].
+	].
     ].
 !
 
-unmapped 
+unmapped
     "the recevier was unmapped (i.e. iconified);
      look for partners and slaves."
 
     |r|
 
     (windowGroup notNil and:[windowGroup isModal]) ifTrue:[
-        "keep the realized flag true (to avoid exiting the modal event loop).
-         Consider this a kludge."
-        self markAsUnmappedModalBox.
-        r := realized.
+	"keep the realized flag true (to avoid exiting the modal event loop).
+	 Consider this a kludge."
+	self markAsUnmappedModalBox.
+	r := realized.
     ] ifFalse:[
-        self unmarkAsUnmappedModalBox.
-        r := realized := false. 
+	self unmarkAsUnmappedModalBox.
+	r := realized := false.
     ].
     super unmapped.
     realized := r.
@@ -1373,7 +1376,11 @@
 !TopView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.127 2009-06-10 13:30:54 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.128 2010-10-11 09:06:49 mb Exp $'
+!
+
+version_CVS
+    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.128 2010-10-11 09:06:49 mb Exp $'
 ! !
 
 TopView initialize!