TopView.st
changeset 5721 c183558179c4
parent 5720 4c3aa29fff39
child 5723 d75bdd85df13
--- a/TopView.st	Thu Mar 03 19:22:14 2011 +0100
+++ b/TopView.st	Thu Mar 03 19:28:16 2011 +0100
@@ -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
@@ -12,15 +12,15 @@
 "{ Package: 'stx:libview' }"
 
 View subclass:#TopView
-        instanceVariableNames:'type iconified keyboardProcessor'
-        classVariableNames:'TakeFocusWhenMapped ForceModalBoxesToOpenAtCenter
-                ForceModalBoxesToOpenAtPointer MasterSlaveMask WindowTypeMask
-                TypeMaster TypeSlave TypePartner TypeDialog TypePopUp
-                TypeUndecorated TypeToolWindow TypeToolDialog MDIClientMask
-                MDIClient TypeScreenDialog CurrentWindowMoveStart
-                CurrentWindowMoveState CurrentWindowBeingMoved'
-        poolDictionaries:''
-        category:'Views-Basic'
+	instanceVariableNames:'type iconified keyboardProcessor'
+	classVariableNames:'TakeFocusWhenMapped ForceModalBoxesToOpenAtCenter
+		ForceModalBoxesToOpenAtPointer MasterSlaveMask WindowTypeMask
+		TypeMaster TypeSlave TypePartner TypeDialog TypePopUp
+		TypeUndecorated TypeToolWindow TypeToolDialog MDIClientMask
+		MDIClient TypeScreenDialog CurrentWindowMoveStart
+		CurrentWindowMoveState CurrentWindowBeingMoved'
+	poolDictionaries:''
+	category:'Views-Basic'
 !
 
 !TopView class methodsFor:'documentation'!
@@ -28,7 +28,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
@@ -48,21 +48,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
 "
 !
 
@@ -76,108 +76,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]
 
 "
 ! !
@@ -228,7 +228,7 @@
 
     display := Screen current.
     display isNil ifTrue:[
-        ^ 600 @ 400
+	^ 600 @ 400
     ].
     ^ display defaultExtentForTopViews
 !
@@ -323,8 +323,8 @@
 
     "/ 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
 !
@@ -336,8 +336,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
 !
@@ -354,8 +354,8 @@
 
     "/ 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
 
@@ -372,8 +372,8 @@
 
     "/ 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
 
@@ -399,8 +399,8 @@
 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
 !
@@ -422,8 +422,8 @@
 
     "/ 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
 !
@@ -435,8 +435,8 @@
 
     "/ 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
 
@@ -463,8 +463,8 @@
 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
 !
@@ -472,8 +472,8 @@
 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
 !
@@ -483,8 +483,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
 !
@@ -493,7 +493,7 @@
     "define the sequence for stepping through my components."
 
     windowGroup isNil ifTrue:[
-        windowGroup := self windowGroupClass new.
+	windowGroup := self windowGroupClass new.
     ].
     windowGroup focusSequence:aCollectionOfSubcomponents.
 
@@ -518,9 +518,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|
@@ -542,26 +542,26 @@
      StandardSystemViewController."
 
     <resource: #keyboard ( #Tab
-                           #FocusNext #FocusPrevious
-                           #CursorDown #CursorUp ) >
+			   #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
@@ -721,9 +721,9 @@
 
     (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.
     ].
 !
 
@@ -735,28 +735,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"
@@ -807,7 +807,7 @@
     super postRealize.
 
     keyboardProcessor isNil ifTrue:[
-        keyboardProcessor := KeyboardProcessor new.
+	keyboardProcessor := KeyboardProcessor new.
     ].
 
     device realizedTopViewHookFor:self
@@ -815,56 +815,30 @@
 
 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
 ! !
 
 !TopView methodsFor:'misc'!
 
-doWindowMove
-    "a window move operation"
-
-    |delta|
-
-    CurrentWindowMoved == self ifTrue:[
-        delta := device pointerPosition - CurrentWindowMoveStart.
-        (CurrentWindowMoveState notNil
-        or:[ delta r > 5 ]) ifTrue:[
-            CurrentWindowMoveState := #inMove.
-            CurrentWindowMoveStart := device pointerPosition.
-            self origin:(self origin + delta).
-        ].
-    ].
-
-    "Created: / 03-03-2011 / 19:13:08 / cg"
-!
-
-endWindowMove
-    "a window wants to stop a move operation"
-
-    CurrentWindowMoved := nil.
-
-    "Created: / 03-03-2011 / 19:17:24 / cg"
-!
-
 raiseDeiconified
     "deiconify & bring to front"
 
     self isCollapsed ifTrue:[
 "/        self unmap.
-        self realize.
+	self realize.
     ].
     self raise
 
@@ -875,16 +849,6 @@
     "Modified: 3.5.1996 / 23:49:36 / stefan"
 !
 
-startWindowMove
-    "a window wants to start a move operation"
-
-    CurrentWindowMoved := self.
-    CurrentWindowMoveStart := device pointerPosition.
-    CurrentWindowMoveState := nil.
-
-    "Created: / 03-03-2011 / 19:09:39 / cg"
-!
-
 waitUntilClosed
     "wait until the receiver has been closed.
      Can be used to synchronize multiple-window applications,
@@ -892,7 +856,7 @@
      when invoking commands with the rDoit mechanism"
 
     [drawableId isNil] whileFalse:[
-        Delay waitForSeconds:0.1.
+	Delay waitForSeconds:0.1.
     ].
 
     "asynchronous:
@@ -913,7 +877,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
 ! !
@@ -956,7 +920,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
@@ -970,7 +934,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
@@ -987,7 +951,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
@@ -1024,7 +988,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
@@ -1084,12 +1048,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
 
@@ -1110,13 +1074,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
@@ -1128,7 +1092,7 @@
     "added bell to wake up user"
 
     (self beepWhenOpening) ifTrue:[
-        self beep.
+	self beep.
     ].
     super openModal
 
@@ -1185,25 +1149,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.
 !
@@ -1213,8 +1177,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
 !
@@ -1224,14 +1188,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"
@@ -1284,10 +1248,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.
@@ -1342,9 +1306,9 @@
      Added for ST-80 compatibility"
 
     self
-        origin:aBoundaryRectangle origin;
-        extent:aBoundaryRectangle extent;
-        sizeFixed:true.
+	origin:aBoundaryRectangle origin;
+	extent:aBoundaryRectangle extent;
+	sizeFixed:true.
     self open
 
     "Modified: 12.2.1997 / 11:58:21 / cg"
@@ -1452,18 +1416,18 @@
      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]].
+	].
     ].
 !
 
@@ -1474,13 +1438,13 @@
     |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.
@@ -1496,11 +1460,11 @@
 !TopView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.138 2011-03-03 18:22:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.139 2011-03-03 18:28:16 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.138 2011-03-03 18:22:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview/TopView.st,v 1.139 2011-03-03 18:28:16 cg Exp $'
 ! !
 
 TopView initialize!