Multi Screen Support
authorMichael Beyl <mb@exept.de>
Mon, 11 Oct 2010 11:07:28 +0200
changeset 2870 7ba0a201bbc6
parent 2869 fd029e1ec24c
child 2871 e9df4227a57d
Multi Screen Support
WindowBuilder.st
--- a/WindowBuilder.st	Fri Oct 01 14:44:54 2010 +0200
+++ b/WindowBuilder.st	Mon Oct 11 11:07:28 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
@@ -25,7 +25,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
@@ -43,9 +43,9 @@
     some interface spec.
 
     The order of the lookup sequence to access an aspect is defined:
-        application
-        application class
-        additional  class (applicationClass).
+	application
+	application class
+	additional  class (applicationClass).
 
     Methods to access any aspect are located in the category
     'spec creation aspect fetch'.
@@ -55,73 +55,73 @@
     specs - thinking of motifs UIL specs, Windows DialogSpecs etc.).
 
     [instance variables:]
-        window          <View>
-                                the topView into which the components
-                                are (have been) created from the specification
-                                
-        application     <ApplicationModel>
-                                the application object (typically an instance
-                                of a subclass of ApplicationModel).
-                                That one is usually supposed to provide
-                                valueHolders for aspects, action methods
-                                menuSpecs and possibly more windowSpecs.
-                                Usually means, that most of those can also be
-                                provided to the builder via a set of bindings,
-                                which overrides those.
+	window          <View>
+				the topView into which the components
+				are (have been) created from the specification
+
+	application     <ApplicationModel>
+				the application object (typically an instance
+				of a subclass of ApplicationModel).
+				That one is usually supposed to provide
+				valueHolders for aspects, action methods
+				menuSpecs and possibly more windowSpecs.
+				Usually means, that most of those can also be
+				provided to the builder via a set of bindings,
+				which overrides those.
 
-        bindings        <Dictionary>
-                                can be set (or filled) with bindings for
-                                aspects to be used when setting up the models
-                                for components. Useful either to overwrite
-                                corresponding appModel aspects or if the appModel
-                                does not want to procide those.
-                                (for example, to open a dialog and provide the
-                                 bindings in a dictionary - as opposed to
-                                 providing them via aspect methods)
+	bindings        <Dictionary>
+				can be set (or filled) with bindings for
+				aspects to be used when setting up the models
+				for components. Useful either to overwrite
+				corresponding appModel aspects or if the appModel
+				does not want to procide those.
+				(for example, to open a dialog and provide the
+				 bindings in a dictionary - as opposed to
+				 providing them via aspect methods)
 
-        visuals                 not yet used - for compatibility
+	visuals                 not yet used - for compatibility
 
-        focusSequence   <Collection>
-                                maintained during the build process;
-                                contains tabable components.
-                                This will be replaced by a more intelligent
-                                mechanism in the near future.
+	focusSequence   <Collection>
+				maintained during the build process;
+				contains tabable components.
+				This will be replaced by a more intelligent
+				mechanism in the near future.
 
-        namedComponents <Dictionary>
-                                contains name->component associations for
-                                all components which have a non-nil component
-                                name. Created during the build process.
+	namedComponents <Dictionary>
+				contains name->component associations for
+				all components which have a non-nil component
+				name. Created during the build process.
 
-        helpKeys                not yet used - for compatibility
+	helpKeys                not yet used - for compatibility
 
-        componentCreationHook <BlockOrNil>
-                                can be set before the components are built
-                                from the spec, to provide an arbitrary
-                                callBacks-hook which will be invoked after
-                                a component has been created from a spec. 
-                                The UIPainter uses this to maintain its
-                                component<->spec assiciations.
-                                Can be set by the app, to catch creation of
-                                components and fiddle around during the
-                                creation process (change extents, colors or whatever)
+	componentCreationHook <BlockOrNil>
+				can be set before the components are built
+				from the spec, to provide an arbitrary
+				callBacks-hook which will be invoked after
+				a component has been created from a spec.
+				The UIPainter uses this to maintain its
+				component<->spec assiciations.
+				Can be set by the app, to catch creation of
+				components and fiddle around during the
+				creation process (change extents, colors or whatever)
 
-        applicationClass <ClassOrNil>
-                                can be set to provide an additional class which
-                                is asked for aspects during the build process.
-                                If not set, the app is asked, which itself asks
-                                its class.
+	applicationClass <ClassOrNil>
+				can be set to provide an additional class which
+				is asked for aspects during the build process.
+				If not set, the app is asked, which itself asks
+				its class.
 
-        keyboardProcessor       not yet used - for compatibility
-                                Will eventually takeover the functionality
-                                of the focusSequence, shortcuts & provide a hook
-                                for the app.
-        
-        subCanvasSpecs <Dictionary>
-                                can be set by the app to provide subcanvas
-                                specs (much like the bindings dictionary)
+	keyboardProcessor       not yet used - for compatibility
+				Will eventually takeover the functionality
+				of the focusSequence, shortcuts & provide a hook
+				for the app.
+
+	subCanvasSpecs <Dictionary>
+				can be set by the app to provide subcanvas
+				specs (much like the bindings dictionary)
 
     [author:]
-        Claus Gittinger
+	Claus Gittinger
 "
 ! !
 
@@ -173,10 +173,10 @@
      All bindings from moreBindings overwrite any local bindings."
 
     moreBindings notNil ifTrue:[
-        bindings isNil ifTrue:[
-            bindings := IdentityDictionary new
-        ].
-        bindings addAll:moreBindings
+	bindings isNil ifTrue:[
+	    bindings := IdentityDictionary new
+	].
+	bindings addAll:moreBindings
     ]
 
     "Created: 28.2.1997 / 14:14:33 / cg"
@@ -205,17 +205,17 @@
 applicationClass
     "return the value of the instance variable 'applicationClass' (automatically generated).
      WARNING:
-        This is a private interface for the UIPainter to pass down the app-class
-        to the specs when editing."
+	This is a private interface for the UIPainter to pass down the app-class
+	to the specs when editing."
 
-    ^ applicationClass 
+    ^ applicationClass
 !
 
 applicationClass:something
     "set the value of the instance variable 'applicationClass' (automatically generated).
      WARNING:
-         This is a private interface for the UIPainter to pass down the app-class
-         to the specs when editing."
+	 This is a private interface for the UIPainter to pass down the app-class
+	 to the specs when editing."
 
     applicationClass := something.
 !
@@ -223,9 +223,9 @@
 aspectAt:aSymbol
     "return the aspect for a symbol or nil."
 
-    ^ self 
-        aspectAt:aSymbol 
-        ifAbsent:[self aspectNotFound:aSymbol error:'no aspect for:']
+    ^ self
+	aspectAt:aSymbol
+	ifAbsent:[self aspectNotFound:aSymbol error:'no aspect for:']
 
     "Modified: / 4.8.1998 / 19:29:36 / cg"
 !
@@ -236,25 +236,25 @@
     |b|
 
     aSymbol notNil ifTrue:[
-        bindings notNil ifTrue:[
-            b := bindings at:aSymbol ifAbsent:nil.
-            b notNil ifTrue:[^ b].
-        ].
+	bindings notNil ifTrue:[
+	    b := bindings at:aSymbol ifAbsent:nil.
+	    b notNil ifTrue:[^ b].
+	].
 
-        application notNil ifTrue:[
-            MessageNotUnderstood 
-                ignoreNotUnderstoodOf:aSymbol
-                in:[
-                    ^ application aspectFor:aSymbol
-                ].
-            MessageNotUnderstood 
-                ignoreNotUnderstoodOf:aSymbol
-                in:[
-                    ^ application class aspectFor:aSymbol
-                ].
+	application notNil ifTrue:[
+	    MessageNotUnderstood
+		ignoreNotUnderstoodOf:aSymbol
+		in:[
+		    ^ application aspectFor:aSymbol
+		].
+	    MessageNotUnderstood
+		ignoreNotUnderstoodOf:aSymbol
+		in:[
+		    ^ application class aspectFor:aSymbol
+		].
 
-            ^ exceptionBlock value.
-        ]
+	    ^ exceptionBlock value.
+	]
     ].
     ^ nil
 
@@ -267,7 +267,7 @@
      Returns the stored aspect !!"
 
     bindings isNil ifTrue:[
-        bindings := IdentityDictionary new
+	bindings := IdentityDictionary new
     ].
     bindings at:aSymbol put:aModel.
     ^ aModel
@@ -277,7 +277,7 @@
     "return the binding for a symbol or nil if there is none"
 
     bindings notNil ifTrue:[
-        ^ bindings at:aSymbol ifAbsent:nil.
+	^ bindings at:aSymbol ifAbsent:nil.
     ].
     ^ nil
 !
@@ -303,8 +303,8 @@
     |widget|
 
     namedComponents notNil ifTrue:[
-        widget := namedComponents at:name asSymbol ifAbsent:nil.
-        widget notNil ifTrue:[^ widget].
+	widget := namedComponents at:name asSymbol ifAbsent:nil.
+	widget notNil ifTrue:[^ widget].
     ].
 
     "/ cg the following code looks in any application-
@@ -319,14 +319,14 @@
 "/        |appBuilder masterApplication masterBuilder|
 "/
 "/        (appBuilder := application builder) notNil ifTrue:[
-"/            appBuilder ~~ self ifTrue:[    
+"/            appBuilder ~~ self ifTrue:[
 "/                ^ appBuilder componentAt:name
 "/            ]
 "/        ].
 "/
 "/        (masterApplication := application masterApplication) notNil ifTrue:[
 "/            (masterBuilder := masterApplication builder) notNil ifTrue:[
-"/                masterBuilder ~~ self ifTrue:[    
+"/                masterBuilder ~~ self ifTrue:[
 "/                    ^ masterBuilder componentAt:name
 "/                ]
 "/            ]
@@ -339,7 +339,7 @@
     "store a component identified by its name."
 
     namedComponents isNil ifTrue:[
-        namedComponents := IdentityDictionary new.
+	namedComponents := IdentityDictionary new.
     ].
     namedComponents at:name asSymbol put:aComponent
 !
@@ -360,7 +360,7 @@
     "/ self assert:(aSpec isKindOf:UISpecification).
 
     componentToSpecMapping isNil ifTrue:[
-        componentToSpecMapping := IdentityDictionary new.
+	componentToSpecMapping := IdentityDictionary new.
     ].
     componentToSpecMapping at:aView put:aSpec
 !
@@ -369,10 +369,10 @@
     "recursively search for a component identified by its name in myself
      and all of my subApplications."
 
-    ^ self 
-        findComponentAt:name 
-        forWhichViewConformsTo:[:v | true]
-        ignoringViews:(IdentitySet new).
+    ^ self
+	findComponentAt:name
+	forWhichViewConformsTo:[:v | true]
+	ignoringViews:(IdentitySet new).
 !
 
 findComponentAt:name forWhichViewConformsTo:viewCheck ignoringViews:triedViews
@@ -385,11 +385,11 @@
     |comp "window" app b|
 
     (comp := self componentAt:name) notNil ifTrue:[
-        ^ comp
+	^ comp
     ].
 
     window isNil ifTrue:[
-        ^ self
+	^ self
     ].
     "/ window := self application window.
 
@@ -397,20 +397,20 @@
     triedViews add:window.
 
     window allSubViewsDo:[:v |
-        (triedViews includes:v) ifFalse:[
-            triedViews add:v.
-            (viewCheck value:v) ifTrue:[
-                ((app := v application) notNil 
-                and:[(b := app builder) notNil 
-                and:[b ~~ self]])
-                ifTrue:[
-                    comp := b findComponentAt:name forWhichViewConformsTo:viewCheck ignoringViews:triedViews.
-                    comp notNil ifTrue:[
-                        ^ comp
-                    ]
-                ]
-            ]
-        ]
+	(triedViews includes:v) ifFalse:[
+	    triedViews add:v.
+	    (viewCheck value:v) ifTrue:[
+		((app := v application) notNil
+		and:[(b := app builder) notNil
+		and:[b ~~ self]])
+		ifTrue:[
+		    comp := b findComponentAt:name forWhichViewConformsTo:viewCheck ignoringViews:triedViews.
+		    comp notNil ifTrue:[
+			^ comp
+		    ]
+		]
+	    ]
+	]
     ].
     ^ nil
 !
@@ -420,10 +420,10 @@
      and all of my subApplications.
      Be careful: this also searches for components in unmapped canvases."
 
-    ^ self 
-        findComponentAt:name 
-        forWhichViewConformsTo:[:v | v shown]
-        ignoringViews:(IdentitySet new).
+    ^ self
+	findComponentAt:name
+	forWhichViewConformsTo:[:v | v shown]
+	ignoringViews:(IdentitySet new).
 !
 
 helpKeyFor:aComponent
@@ -433,15 +433,15 @@
 
     v := aComponent.
     [v notNil] whileTrue:[
-        (key := v helpKey) notNil ifTrue:[
-            ^ key
-        ].
+	(key := v helpKey) notNil ifTrue:[
+	    ^ key
+	].
 "/        helpKeys notNil ifTrue:[
 "/            (key := helpKeys at:v ifAbsent:nil) notNil ifTrue:[
 "/                ^ key
 "/            ].
 "/        ].
-        v := v superView
+	v := v superView
     ].
     ^ nil
 !
@@ -468,7 +468,7 @@
     "return my keyboard processor"
 
     keyboardProcessor isNil ifTrue:[
-        keyboardProcessor := KeyboardProcessor new    
+	keyboardProcessor := KeyboardProcessor new
     ].
     ^ keyboardProcessor
 
@@ -493,7 +493,7 @@
 
 labelAt:name put:aLabelString
     labels isNil ifTrue:[
-        labels := IdentityDictionary new.
+	labels := IdentityDictionary new.
     ].
     labels at:name asSymbol put:aLabelString
 
@@ -501,7 +501,7 @@
 !
 
 menuAt:aKey
-    "Find a binding for the menu named aKey, either in the bindings 
+    "Find a binding for the menu named aKey, either in the bindings
      or from the source"
 
     ^ self menuFor:aKey
@@ -524,18 +524,18 @@
 
 namedComponentsDo: aBlock
     namedComponents notNil ifTrue:[
-        namedComponents do:[:aView|
-            aBlock value: aView
-        ]
+	namedComponents do:[:aView|
+	    aBlock value: aView
+	]
     ]
 !
 
 resources
-    "return the applications resources - 
+    "return the applications resources -
      that's a ResourcePack containing national language strings"
 
     application notNil ifTrue:[
-        ^ application resources
+	^ application resources
     ].
     ^ Dialog classResources.
 !
@@ -555,44 +555,44 @@
     minorKey isNil ifTrue:[^ nil].
 
     subCanvasSpecs notNil ifTrue:[
-        dkey := majorKey ? #NoMajorKey.
-        dict := subCanvasSpecs at:dkey ifAbsent:nil.
+	dkey := majorKey ? #NoMajorKey.
+	dict := subCanvasSpecs at:dkey ifAbsent:nil.
 
-        dict notNil ifTrue:[
-            spec := dict at:minorKey ifAbsent:nil.
-            spec notNil ifTrue:[^ spec].
-        ].
+	dict notNil ifTrue:[
+	    spec := dict at:minorKey ifAbsent:nil.
+	    spec notNil ifTrue:[^ spec].
+	].
     ].
 
     majorKey isNil ifTrue:[
-        spec := self specificationFor:minorKey.
-        spec isNil ifTrue:[
-            "fallback for UIPainter"
-            MessageNotUnderstood catch:[
-                spec := applicationClass perform:minorKey.
-            ].
-        ].
-        ^ spec
+	spec := self specificationFor:minorKey.
+	spec isNil ifTrue:[
+	    "fallback for UIPainter"
+	    MessageNotUnderstood catch:[
+		spec := applicationClass perform:minorKey.
+	    ].
+	].
+	^ spec
     ].
 
     application notNil ifTrue:[
-        "/ look for class in applications namespace ...
-        cls := application resolveName:majorKey.
+	"/ look for class in applications namespace ...
+	cls := application resolveName:majorKey.
     ] ifFalse:[
-        "/ fallBack - use that global, if it exists
-        cls := Smalltalk at:majorKey.
-        cls isNil ifTrue:[
-            Transcript showCR:('WindowBuilder[warning]: missing application when fetching majorKey:' , majorKey).
-        ].
+	"/ fallBack - use that global, if it exists
+	cls := Smalltalk at:majorKey.
+	cls isNil ifTrue:[
+	    Transcript showCR:('WindowBuilder[warning]: missing application when fetching majorKey:' , majorKey).
+	].
     ].
 
     cls notNil ifTrue:[
-        MessageNotUnderstood catch:[
-            ^ cls specificationFor:minorKey
-        ].
-        MessageNotUnderstood catch:[
-            ^ cls perform:minorKey.
-        ]
+	MessageNotUnderstood catch:[
+	    ^ cls specificationFor:minorKey
+	].
+	MessageNotUnderstood catch:[
+	    ^ cls perform:minorKey.
+	]
     ].
     ^ nil
 !
@@ -600,7 +600,7 @@
 subCanvasAt:majorKey at:minorKey put:aSpec
     "deposit an interfaceSpecification for major and minor key
      in my private subCanvasSpecs dictionary.
-     This will be used later, when building, 
+     This will be used later, when building,
      to provide an interfaceSpec for a subcanvas or subSpecification
      (or possibly override an application provided interfaceSpec).
      See #subCanvasAt:at:."
@@ -608,15 +608,15 @@
     |dict key|
 
     subCanvasSpecs isNil ifTrue:[
-        "/ lazyly initialize
-        subCanvasSpecs := IdentityDictionary new
+	"/ lazyly initialize
+	subCanvasSpecs := IdentityDictionary new
     ].
 
     key := majorKey ? #NoMajorKey.
     dict := subCanvasSpecs at:key ifAbsent:nil.
     dict isNil ifTrue:[
-        dict := IdentityDictionary new.
-        subCanvasSpecs at:key put:dict
+	dict := IdentityDictionary new.
+	subCanvasSpecs at:key put:dict
     ].
     dict at:minorKey put:aSpec
 
@@ -633,7 +633,7 @@
 
 visualAt:name put:aVisual
     visuals isNil ifTrue:[
-        visuals := IdentityDictionary new.
+	visuals := IdentityDictionary new.
     ].
     visuals at:name asSymbol put:aVisual
 
@@ -697,7 +697,7 @@
     |list|
 
     (list := self bindingAt:aKey) isNil ifTrue:[
-        self aspectAt:aKey put:(list := List new).
+	self aspectAt:aKey put:(list := List new).
     ].
     ^ list
 
@@ -726,7 +726,7 @@
     |holder|
 
     (holder := self bindingAt:aKey) isNil ifTrue:[
-        self aspectAt:aKey put:(holder := initialValueBlock value asValue).
+	self aspectAt:aKey put:(holder := initialValueBlock value asValue).
     ].
     ^ holder
 !
@@ -740,7 +740,7 @@
     |holder|
 
     (holder := self bindingAt:aKey) isNil ifTrue:[
-        self aspectAt:aKey put:(holder := initialValue asValue).
+	self aspectAt:aKey put:(holder := initialValue asValue).
     ].
     ^ holder
 
@@ -772,14 +772,14 @@
      and/or stop (if StopOnError) is true"
 
     Verbose == true ifTrue:[
-        Transcript showCR:('WindowBuilder: %1 aspect: <%2>' bindWith:aString with:anAspect storeString).
-        application notNil ifTrue:[
-             Transcript showCR:('WindowBuilder: (while building for %1)' bindWith:application class name).
-        ].
+	Transcript showCR:('WindowBuilder: %1 aspect: <%2>' bindWith:aString with:anAspect storeString).
+	application notNil ifTrue:[
+	     Transcript showCR:('WindowBuilder: (while building for %1)' bindWith:application class name).
+	].
     ].
 
     StopOnError == true ifTrue:[
-        self halt:'aspect not found'        "/ set StopOnError to true to debug end-user apps
+	self halt:'aspect not found'        "/ set StopOnError to true to debug end-user apps
     ].
     ^ nil
 
@@ -795,29 +795,29 @@
     |handlerBlock|
 
     aSelector notNil ifTrue:[
-        handlerBlock := [:ex| 
-                            (ex selector ~~ aSelector) ifTrue:[
-                                ex reject
-                            ]
-                        ].
+	handlerBlock := [:ex|
+			    (ex selector ~~ aSelector) ifTrue:[
+				ex reject
+			    ]
+			].
 
-        application notNil ifTrue:[
-            MessageNotUnderstood handle:handlerBlock do:[
-                ^ application perform:aSelector
-            ].
-            MessageNotUnderstood handle:handlerBlock do:[
-                ^ application class perform:aSelector
-            ]
-        ].
-        "
-         WARNING:
-            This is a private interface for the UIPainter to pass down the app-class
-        "
-        applicationClass notNil ifTrue:[
-            MessageNotUnderstood handle:handlerBlock do:[
-                ^ applicationClass perform:aSelector
-            ]
-        ]
+	application notNil ifTrue:[
+	    MessageNotUnderstood handle:handlerBlock do:[
+		^ application perform:aSelector
+	    ].
+	    MessageNotUnderstood handle:handlerBlock do:[
+		^ application class perform:aSelector
+	    ]
+	].
+	"
+	 WARNING:
+	    This is a private interface for the UIPainter to pass down the app-class
+	"
+	applicationClass notNil ifTrue:[
+	    MessageNotUnderstood handle:handlerBlock do:[
+		^ applicationClass perform:aSelector
+	    ]
+	]
     ].
     ^ aBlock value
 
@@ -828,30 +828,30 @@
     "send the one-arg-message aSelector to the application;
      the result returned from the send or nil is returned"
 
-    ^ self 
-        safelyPerform:aSelector 
-        withArguments:(Array with:anArgument) 
-        ifNone:aBlock
+    ^ self
+	safelyPerform:aSelector
+	withArguments:(Array with:anArgument)
+	ifNone:aBlock
 !
 
 safelyPerform:aSelector with:arg1 with:arg2 ifNone:aBlock
     "send the two-arg-message aSelector to the application;
      the result returned from the send or nil is returned"
 
-    ^ self 
-        safelyPerform:aSelector 
-        withArguments:(Array with:arg1 with:arg2) 
-        ifNone:aBlock
+    ^ self
+	safelyPerform:aSelector
+	withArguments:(Array with:arg1 with:arg2)
+	ifNone:aBlock
 !
 
 safelyPerform:aSelector with:arg1 with:arg2 with:arg3 ifNone:aBlock
     "send the 3-arg-message aSelector to the application;
      the result returned from the send or nil is returned"
 
-    ^ self 
-        safelyPerform:aSelector 
-        withArguments:(Array with:arg1 with:arg2 with:arg3) 
-        ifNone:aBlock
+    ^ self
+	safelyPerform:aSelector
+	withArguments:(Array with:arg1 with:arg2 with:arg3)
+	ifNone:aBlock
 !
 
 safelyPerform:aSelector withArguments:arguments ifNone:aBlock
@@ -861,30 +861,30 @@
     |handlerBlock|
 
     aSelector notNil ifTrue:[
-        handlerBlock := [:ex| |badSel|
-                            badSel := ex selector.
-                            (badSel ~~ aSelector and:[badSel ~~ arguments first]) ifTrue:[
-                                ex reject
-                            ]
-                        ].
+	handlerBlock := [:ex| |badSel|
+			    badSel := ex selector.
+			    (badSel ~~ aSelector and:[badSel ~~ arguments first]) ifTrue:[
+				ex reject
+			    ]
+			].
 
-        application notNil ifTrue:[
-            MessageNotUnderstood handle:handlerBlock do:[
-                ^ application perform:aSelector withArguments:arguments
-            ].
-            MessageNotUnderstood handle:handlerBlock do:[
-                ^ application class perform:aSelector withArguments:arguments
-            ]
-        ].
-        "
-         WARNING:
-            This is a private interface for the UIPainter to pass down the app-class
-        "
-        applicationClass notNil ifTrue:[
-            MessageNotUnderstood handle:handlerBlock do:[
-                ^ applicationClass perform:aSelector withArguments:arguments
-            ].
-        ]
+	application notNil ifTrue:[
+	    MessageNotUnderstood handle:handlerBlock do:[
+		^ application perform:aSelector withArguments:arguments
+	    ].
+	    MessageNotUnderstood handle:handlerBlock do:[
+		^ application class perform:aSelector withArguments:arguments
+	    ]
+	].
+	"
+	 WARNING:
+	    This is a private interface for the UIPainter to pass down the app-class
+	"
+	applicationClass notNil ifTrue:[
+	    MessageNotUnderstood handle:handlerBlock do:[
+		^ applicationClass perform:aSelector withArguments:arguments
+	    ].
+	]
     ].
     ^ aBlock value
 
@@ -903,68 +903,68 @@
 
 !WindowBuilder methodsFor:'resolving fonts'!
 
-resolveFont:fontOrSymbolOrStyle 
+resolveFont:fontOrSymbolOrStyle
     "resolve fontOrSymbol to a real font"
 
     |font txtAttribs charAttribs|
 
     fontOrSymbolOrStyle isSymbol ifTrue:[
-        self isEditing ifTrue:[
-            "special for UIPainter setup: check class for color"
-            applicationClass notNil ifTrue:[
-                font := applicationClass fontFor:fontOrSymbolOrStyle.
-            ].
-        ] ifFalse:[    
-            font := application fontFor:fontOrSymbolOrStyle.
-        ].
-        font notNil ifTrue:[
-            ^ font.
-        ].    
+	self isEditing ifTrue:[
+	    "special for UIPainter setup: check class for color"
+	    applicationClass notNil ifTrue:[
+		font := applicationClass fontFor:fontOrSymbolOrStyle.
+	    ].
+	] ifFalse:[
+	    font := application fontFor:fontOrSymbolOrStyle.
+	].
+	font notNil ifTrue:[
+	    ^ font.
+	].
 
-        "/ ST80 style textAttributes
-        (TextAttributes notNil and:[TextAttributes isLoaded]) ifTrue:[
-            txtAttribs := TextAttributes styleNamed:fontOrSymbolOrStyle ifAbsent:nil.
-            txtAttribs notNil ifTrue:[
-                charAttribs := txtAttribs characterAttributes.
-                charAttribs notNil ifTrue:[
-                    font := charAttribs defaultFont.
-                ]
-            ].
-        ].
+	"/ ST80 style textAttributes
+	(TextAttributes notNil and:[TextAttributes isLoaded]) ifTrue:[
+	    txtAttribs := TextAttributes styleNamed:fontOrSymbolOrStyle ifAbsent:nil.
+	    txtAttribs notNil ifTrue:[
+		charAttribs := txtAttribs characterAttributes.
+		charAttribs notNil ifTrue:[
+		    font := charAttribs defaultFont.
+		]
+	    ].
+	].
 
-        font isNil ifTrue:[
-            fontOrSymbolOrStyle == #labelFont ifTrue:[
-                ^ Label defaultFont
-            ].
-            fontOrSymbolOrStyle == #buttonFont ifTrue:[
-                ^ Button defaultFont
-            ].
-            fontOrSymbolOrStyle == #listFont ifTrue:[
-                ^ SelectionInListView defaultFont
-            ].
-            fontOrSymbolOrStyle == #menuFont ifTrue:[
-                ^ MenuView defaultFont
-            ].
-            fontOrSymbolOrStyle == #textFont ifTrue:[
-                ^ TextView defaultFont
-            ].
-            fontOrSymbolOrStyle == #inputFont ifTrue:[
-                ^ EditField defaultFont
-            ].
-        ].
+	font isNil ifTrue:[
+	    fontOrSymbolOrStyle == #labelFont ifTrue:[
+		^ Label defaultFont
+	    ].
+	    fontOrSymbolOrStyle == #buttonFont ifTrue:[
+		^ Button defaultFont
+	    ].
+	    fontOrSymbolOrStyle == #listFont ifTrue:[
+		^ SelectionInListView defaultFont
+	    ].
+	    fontOrSymbolOrStyle == #menuFont ifTrue:[
+		^ MenuView defaultFont
+	    ].
+	    fontOrSymbolOrStyle == #textFont ifTrue:[
+		^ TextView defaultFont
+	    ].
+	    fontOrSymbolOrStyle == #inputFont ifTrue:[
+		^ EditField defaultFont
+	    ].
+	].
 
-        font isNil ifTrue:[
-            ('Missing font <1p> in <2p>' expandMacrosWith:fontOrSymbolOrStyle with:application class) errorPrintCR.
-        ].
-        ^ font.
+	font isNil ifTrue:[
+	    ('Missing font <1p> in <2p>' expandMacrosWith:fontOrSymbolOrStyle with:application class) errorPrintCR.
+	].
+	^ font.
     ].
 
-    ^ Font 
-        family:(fontOrSymbolOrStyle family)
-        face:(fontOrSymbolOrStyle face)
-        style:(fontOrSymbolOrStyle style)
-        size:(fontOrSymbolOrStyle size)
-        encoding:(fontOrSymbolOrStyle encoding)
+    ^ Font
+	family:(fontOrSymbolOrStyle family)
+	face:(fontOrSymbolOrStyle face)
+	style:(fontOrSymbolOrStyle style)
+	size:(fontOrSymbolOrStyle size)
+	encoding:(fontOrSymbolOrStyle encoding)
 ! !
 
 !WindowBuilder methodsFor:'spec creation aspect fetch'!
@@ -979,17 +979,17 @@
     |b|
 
     bindings notNil ifTrue:[
-        b := bindings at:aKey ifAbsent:nil.
-        b notNil ifTrue:[^ b].
+	b := bindings at:aKey ifAbsent:nil.
+	b notNil ifTrue:[^ b].
     ].
 
     ^ self safelyPerform:#actionFor:
-                    with:aKey
-                  ifNone:[ self aspectNotFound:aKey error:'no action for:'. [] ]
+		    with:aKey
+		  ifNone:[ self aspectNotFound:aKey error:'no action for:'. [] ]
 !
 
 actionFor:aKey withValue:aValue
-    "return an action for aKey/value combonation. 
+    "return an action for aKey/value combonation.
      This is invoked during window building
      (by the builder) to ask for an ActionButtons actionBlock if that button
      specified an action with an argument value.
@@ -1000,25 +1000,25 @@
     |b|
 
     bindings notNil ifTrue:[
-        b := bindings at:aKey ifAbsent:nil.
-        b notNil ifTrue:[
-            (b isBlock and:[b numArgs == 1]) ifTrue:[
-                ^ [b value:aValue]
-            ].
-            ^ b
-        ].
+	b := bindings at:aKey ifAbsent:nil.
+	b notNil ifTrue:[
+	    (b isBlock and:[b numArgs == 1]) ifTrue:[
+		^ [b value:aValue]
+	    ].
+	    ^ b
+	].
     ].
 
-    ^ self 
-        safelyPerform:#actionFor:withValue:
-        withArguments:(Array with:aKey with:aValue)
-        ifNone:[ self aspectNotFound:aKey error:'no action for:'. 
-                 [] 
-               ]
+    ^ self
+	safelyPerform:#actionFor:withValue:
+	withArguments:(Array with:aKey with:aValue)
+	ifNone:[ self aspectNotFound:aKey error:'no action for:'.
+		 []
+	       ]
 !
 
 actionFor:aKey withValue:arg1 withValue:arg2
-    "return an action for aKey/value combination. 
+    "return an action for aKey/value combination.
      This is invoked during window building
      (by the builder) to ask for an ActionButtons actionBlock if that button
      specified an action with an argument value.
@@ -1029,19 +1029,19 @@
     |b|
 
     bindings notNil ifTrue:[
-        b := bindings at:aKey ifAbsent:nil.
-        b notNil ifTrue:[
-            (b isBlock and:[b numArgs == 2]) ifTrue:[
-                ^ [b value:arg1 value:arg2]
-            ].
-            ^ b
-        ].
+	b := bindings at:aKey ifAbsent:nil.
+	b notNil ifTrue:[
+	    (b isBlock and:[b numArgs == 2]) ifTrue:[
+		^ [b value:arg1 value:arg2]
+	    ].
+	    ^ b
+	].
     ].
 
-    ^ self 
-        safelyPerform:#actionFor:withValue:withValue:
-        withArguments:(Array with:aKey with:arg1 with:arg2)
-        ifNone:[ self aspectNotFound:aKey error:'no action for:'.  ]
+    ^ self
+	safelyPerform:#actionFor:withValue:withValue:
+	withArguments:(Array with:aKey with:arg1 with:arg2)
+	ifNone:[ self aspectNotFound:aKey error:'no action for:'.  ]
 !
 
 aspectFor:aKey
@@ -1054,14 +1054,14 @@
     |b|
 
     bindings notNil ifTrue:[
-        b := bindings at:aKey ifAbsent:nil.
-        b notNil ifTrue:[^ b].
+	b := bindings at:aKey ifAbsent:nil.
+	b notNil ifTrue:[^ b].
     ].
 
-    ^ self 
-        safelyPerform:#aspectFor:
-        with:aKey
-        ifNone:[ self aspectAt:aKey ]
+    ^ self
+	safelyPerform:#aspectFor:
+	with:aKey
+	ifNone:[ self aspectAt:aKey ]
 !
 
 aspectFor:aKey ifAbsent:exceptionBlock
@@ -1074,14 +1074,14 @@
     |b|
 
     bindings notNil ifTrue:[
-        b := bindings at:aKey ifAbsent:nil.
-        b notNil ifTrue:[^ b].
+	b := bindings at:aKey ifAbsent:nil.
+	b notNil ifTrue:[^ b].
     ].
 
-    ^ self 
-        safelyPerform:#aspectFor:
-        with:aKey
-        ifNone:[ self aspectAt:aKey ifAbsent:exceptionBlock ]
+    ^ self
+	safelyPerform:#aspectFor:
+	with:aKey
+	ifNone:[ self aspectAt:aKey ifAbsent:exceptionBlock ]
 !
 
 componentFor:aKey
@@ -1092,21 +1092,21 @@
      The returned object is typically a view."
 
     ^ self safelyPerform:#componentFor:
-                    with:aKey
-                  ifNone:[ self aspectAt:aKey ]
+		    with:aKey
+		  ifNone:[ self aspectAt:aKey ]
 !
 
-labelFor:aKey 
+labelFor:aKey
     "return a label for aKey. This is invoked during window building
      (by the builder) to ask for a ???'s label.
      Here, first the local bindings are searched, then the application and
      finally the applications class is asked for a corresponding action.
      The returned object is typically a string."
-    
-    ^ self 
-        safelyPerform:#labelFor:
-        with:aKey
-        ifNone:[ self aspectAt:aKey ]
+
+    ^ self
+	safelyPerform:#labelFor:
+	with:aKey
+	ifNone:[ self aspectAt:aKey ]
 !
 
 listFor:aKey
@@ -1117,12 +1117,12 @@
      The returned object is typically a list."
 
     ^ self safelyPerform:#listFor:
-                    with:aKey
-                  ifNone:[ self aspectAt:aKey ]
+		    with:aKey
+		  ifNone:[ self aspectAt:aKey ]
 !
 
 menuFor:aKey
-    "Find a binding for the menu named aKey, either in the bindings 
+    "Find a binding for the menu named aKey, either in the bindings
      or from the source"
 
     |menu|
@@ -1130,24 +1130,24 @@
     aKey isNil ifTrue:[^ nil].
 
     (menu := self bindingAt:aKey) notNil ifTrue:[
-        ^ menu
+	^ menu
     ].
 
     menu := self safelyPerform:#menuFor: with:aKey ifNone:[
-                    self safelyPerform:aKey ifNone:[
-                        self aspectNotFound:aKey error:'no menu for:'.
-                        nil
-                    ]
-                 ].
+		    self safelyPerform:aKey ifNone:[
+			self aspectNotFound:aKey error:'no menu for:'.
+			nil
+		    ]
+		 ].
 
     menu isBlock ifFalse:[
-        ((menu := menu value) notNil and:[application notNil]) ifTrue:[
-            menu isCollection ifTrue:[
-                menu := Menu decodeFromLiteralArray:menu.
-                "/ menu receiver:application. -- now done in findGuiResources ...
-            ].
-            menu findGuiResourcesIn:application
-        ]
+	((menu := menu value) notNil and:[application notNil]) ifTrue:[
+	    menu isCollection ifTrue:[
+		menu := Menu decodeFromLiteralArray:menu.
+		"/ menu receiver:application. -- now done in findGuiResources ...
+	    ].
+	    menu findGuiResourcesIn:application
+	]
     ].
     ^ menu
 
@@ -1161,10 +1161,10 @@
      finally the applications class is asked for a corresponding interfaceSPec.
      The returned object is typically an interfaceSpec array."
 
-    ^ self 
-        safelyPerform:#specificationFor:
-        with:aKey
-        ifNone:[ self aspectFor:aKey ]
+    ^ self
+	safelyPerform:#specificationFor:
+	with:aKey
+	ifNone:[ self aspectFor:aKey ]
 !
 
 visualFor:aKey
@@ -1175,8 +1175,8 @@
      The returned object is typically an image or form."
 
     ^ self safelyPerform:#visualFor:
-                    with:aKey
-                  ifNone:[ self aspectAt:aKey ]
+		    with:aKey
+		  ifNone:[ self aspectAt:aKey ]
 ! !
 
 !WindowBuilder methodsFor:'spec creation callbacks'!
@@ -1194,22 +1194,22 @@
 "/        (namedComponents notNil and:[namedComponents includesKey:name asSymbol]) ifTrue:[
 "/            Transcript showCR:'WARNING multiple UI-build of: ',name asSymbol
 "/        ].
-        self componentAt:name put:aView.
+	self componentAt:name put:aView.
     ].
     spec addView:aView toMappingOfBuilder:self.
     componentCreationHook notNil ifTrue:[
-        componentCreationHook value:aView value:spec value:self
+	componentCreationHook value:aView value:spec value:self
     ].
 
     self isEditing ifFalse:[
-        (createCallBackSelector := spec postBuildCallback) notNil ifTrue:[
-            app := self application.
-            app 
-                perform:createCallBackSelector
-                withOptionalArgument:aView 
-                and:spec 
-                and:self.
-        ].
+	(createCallBackSelector := spec postBuildCallback) notNil ifTrue:[
+	    app := self application.
+	    app
+		perform:createCallBackSelector
+		withOptionalArgument:aView
+		and:spec
+		and:self.
+	].
     ].
 
     "Modified: / 5.9.1995 / 21:42:54 / claus"
@@ -1231,24 +1231,24 @@
     |type|
 
     application isNil ifTrue:[
-        type := #normal
+	type := #normal
     ] ifFalse:[
-        type := application defaultWindowType
+	type := application defaultWindowType
     ].
-    ^ self 
-        openAt:nil 
-        withExtent:nil
-        andType:type
+    ^ self
+	openAt:nil
+	withExtent:nil
+	andType:type
 
 !
 
 openAt:aPoint
     "open my topView at some location"
 
-    ^ self 
-        openAt:aPoint 
-        withExtent:nil  
-        andType:(application defaultWindowType)
+    ^ self
+	openAt:aPoint
+	withExtent:nil
+	andType:(application defaultWindowType)
 
     "Created: 14.2.1997 / 20:21:57 / cg"
     "Modified: 28.2.1997 / 22:50:29 / cg"
@@ -1258,20 +1258,20 @@
     "open my topView, as previously created as a modal view,
      blocking interaction to the currently active view."
 
-    ^ self 
-        openAt:nil 
-        withExtent:nil 
-        andType:#dialog
+    ^ self
+	openAt:nil
+	withExtent:nil
+	andType:#dialog
 !
 
 openDialogAt:aPoint
     "open my topView, as previously created as a modal view,
      blocking interaction to the currently active view."
 
-    ^ self 
-        openAt:aPoint 
-        withExtent:nil 
-        andType:#dialog
+    ^ self
+	openAt:aPoint
+	withExtent:nil
+	andType:#dialog
 
     "Modified: 17.1.1997 / 19:59:36 / cg"
     "Created: 14.2.1997 / 20:24:19 / cg"
@@ -1281,10 +1281,10 @@
     "open my topView, as previously created as a modal view,
      blocking interaction to the currently active view."
 
-    ^ self 
-        openAt:aPoint 
-        withExtent:ext 
-        andType:#dialog
+    ^ self
+	openAt:aPoint
+	withExtent:ext
+	andType:#dialog
 
     "Modified: 17.1.1997 / 19:59:36 / cg"
     "Created: 14.2.1997 / 20:24:19 / cg"
@@ -1294,10 +1294,10 @@
     "open my topView, as previously created as a modal view,
      blocking interaction to the currently active view."
 
-    ^ self 
-        openAt:nil 
-        withExtent:ext 
-        andType:#dialog
+    ^ self
+	openAt:nil
+	withExtent:ext
+	andType:#dialog
 
     "Modified: 17.1.1997 / 19:59:36 / cg"
 !
@@ -1306,10 +1306,10 @@
     "open my topView as a modal dialog, as previously created,
      blocking interaction to the currently active view."
 
-    ^ self 
-        openAt:nil 
-        withExtent:nil 
-        andType:#dialog
+    ^ self
+	openAt:nil
+	withExtent:nil
+	andType:#dialog
 
     "Modified: 3.3.1997 / 19:43:57 / cg"
 !
@@ -1318,10 +1318,10 @@
     "open my topView, as previously created as a popUp view,
      blocking interaction to the currently active view."
 
-    ^ self 
-        openAt:aPoint
-        withExtent:nil 
-        andType:#popUp
+    ^ self
+	openAt:aPoint
+	withExtent:nil
+	andType:#popUp
 
     "Modified: 17.1.1997 / 19:59:29 / cg"
     "Created: 14.2.1997 / 20:24:38 / cg"
@@ -1331,19 +1331,19 @@
     "open my topView, as previously created as a popUp view,
      blocking interaction to the currently active view."
 
-    ^ self 
-        openAt:aRectangle origin
-        withExtent:aRectangle extent 
-        andType:#popUp
+    ^ self
+	openAt:aRectangle origin
+	withExtent:aRectangle extent
+	andType:#popUp
 !
 
 openWindow
     "open my topView"
 
     ^ self
-        openAt:nil 
-        withExtent:nil  
-        andType:(application defaultWindowType)
+	openAt:nil
+	withExtent:nil
+	andType:(application defaultWindowType)
 
 !
 
@@ -1351,32 +1351,32 @@
     "open my topView at some location"
 
     ^ self
-        openAt:aPoint 
-        withExtent:nil  
-        andType:(application defaultWindowType)
+	openAt:aPoint
+	withExtent:nil
+	andType:(application defaultWindowType)
 
 !
 
 openWindowAt:origin withExtent:ext andType:type
     "open my window, as previously created, optionally defining the
-     windows origin and/or extent. 
-     The type argument may be #dialog or #normal, and specifies if the view 
-     should be opened as a modal view, blocking interaction to the currently 
+     windows origin and/or extent.
+     The type argument may be #dialog or #normal, and specifies if the view
+     should be opened as a modal view, blocking interaction to the currently
      active view, or as a normal view."
 
-    ^ self 
-        openAt:origin 
-        withExtent:ext
-        andType:type
+    ^ self
+	openAt:origin
+	withExtent:ext
+	andType:type
 !
 
 openWindowCenter
     "open my topView centered on the screen (dialog & normal only)"
 
     ^ self
-        openAt:#center 
-        withExtent:nil  
-        andType:(application defaultWindowType)
+	openAt:#center
+	withExtent:nil
+	andType:(application defaultWindowType)
 
 !
 
@@ -1384,10 +1384,10 @@
     "open my topView, as previously created, but override
      the extent."
 
-    ^ self 
-        openAt:nil 
-        withExtent:aPoint 
-        andType:(application defaultWindowType)
+    ^ self
+	openAt:nil
+	withExtent:aPoint
+	andType:(application defaultWindowType)
 
     "Modified: 17.1.1997 / 19:58:48 / cg"
 !
@@ -1395,13 +1395,13 @@
 openWithExtent:ext andType:type
     "open my window, as previously created. The type argument
      may be #dialog or #normal, and specifies if the view should
-     be opened as a modal view, blocking interaction to the currently 
+     be opened as a modal view, blocking interaction to the currently
      active view, or as a normal view."
 
-    ^ self 
-        openAt:nil 
-        withExtent:ext 
-        andType:type
+    ^ self
+	openAt:nil
+	withExtent:ext
+	andType:type
 
     "Modified: 14.2.1997 / 20:22:47 / cg"
 ! !
@@ -1410,79 +1410,123 @@
 
 openAt:origin withExtent:ext andType:type
     "open my window, as previously created, optionally defining the
-     windows origin and/or extent. 
-     The type argument may be #dialog, #popup or #normal, 
-     and specifies if the view should be opened as a 
-        modal view (blocking interaction to the currently active view), 
-        as popUp (also blocking)
-        or as a normal view."
+     windows origin and/or extent.
+     The type argument may be #dialog, #popup or #normal,
+     and specifies if the view should be opened as a
+	modal view (blocking interaction to the currently active view),
+	as popUp (also blocking)
+	or as a normal view."
 
-    |appWinClass device wg mainWin usableHeight y|
+    |appWinClass device wg mainWin x y monitorBounds|
 
     device := window device.
-    origin notNil ifTrue:[
-        "/ kludge
-        origin ~~ #center ifTrue:[
-            window origin:origin
-        ]
+
+"/ ********* MULTI SCREEN
+
+    wg := WindowGroup activeGroup.
+
+    wg notNil ifTrue:[
+	|mainGroup focusView|
+
+	mainGroup := wg mainGroup ? wg.
+	focusView := mainGroup focusView.
+	focusView notNil ifTrue:[
+	    mainWin := focusView topView
+	] ifFalse:[
+	    mainWin := mainGroup topViews firstIfEmpty:nil
+	].
     ].
-    ext notNil ifTrue:[
-        window extent:ext.
+
+    origin isPoint ifTrue:[
+	monitorBounds := device monitorBoundsAt:origin.
+	window origin:origin.
     ] ifFalse:[
-        ((type == #dialog) or:[type == #toolDialog]) ifTrue:[
-            window fixSize
-        ]
+	mainWin isNil ifTrue:[
+	    monitorBounds := device monitorBoundsAt:(device pointerPosition).
+	] ifFalse:[
+	    monitorBounds := device monitorBoundsAt:(mainWin origin).
+	].
+    ].
+
+    ext notNil ifTrue:[
+	window extent:ext.
+    ] ifFalse:[
+	((type == #dialog) or:[type == #toolDialog]) ifTrue:[
+	    window fixSize
+	]
     ].
 
     ((type == #dialog) or:[type == #toolDialog]) ifTrue:[
-        ((origin isNil and:[window class forceModalBoxesToOpenAtCenter])
-         or:[origin == #center]) ifTrue:[
-            window origin:((device center - (window extent // 2)) max:0@0)
-        ] ifFalse:[
-            wg := WindowGroup activeGroup.
-            wg notNil ifTrue:[ 
-                wg := wg mainGroup.
-                mainWin := wg topViews firstIfEmpty:nil.
-            ].
-            mainWin notNil ifTrue:[
-                window origin:((mainWin center - (window extent // 2)) max:0@0)
-            ] ifFalse:[
-                window fixPosition:(device pointerPosition - window positionOffset).
-            ]
-        ].
+	|newOrigin|
 
-        usableHeight := window device usableHeightAt:window origin.
-        window corner y > usableHeight ifTrue:[
-            y := usableHeight - window height.
-            window origin:(window origin x @ (y max:0))
-        ].
-        ^ window openModal.
+	((origin isNil and:[window class forceModalBoxesToOpenAtCenter])
+	 or:[origin == #center]) ifTrue:[
+	    newOrigin := nil.
+	] ifFalse:[
+	    origin isPoint ifTrue:[
+		newOrigin := origin
+	    ] ifFalse:[
+		mainWin notNil ifTrue:[
+		    newOrigin := mainWin bounds center rounded - (window extent // 2).
+		]
+	    ]
+	].
+
+	newOrigin isNil ifTrue:[
+	    newOrigin := monitorBounds center rounded - (window extent // 2).
+	].
+	window origin:newOrigin.
+
+	window corner y > monitorBounds bottom ifTrue:[
+	    y := monitorBounds bottom - window height.
+	    window origin:(window origin x @ y).
+	].
+	^ window openModal.
     ].
 
     (type == #normal or:[type = #slave or:[type = #partner]]) ifTrue:[
-        window isNil ifTrue:[
-            application notNil ifTrue:[
-                appWinClass := application applicationWindowClass
-            ] ifFalse:[
-                appWinClass := ApplicationWindow
-            ].
-            self setupWindowFor:appWinClass new.
-        ].
-        origin == #center ifTrue:[
-            window origin:((device center - (window extent // 2)) max:0@0)
-        ].
+	window isNil ifTrue:[
+	    application notNil ifTrue:[
+		appWinClass := application applicationWindowClass
+	    ] ifFalse:[
+		appWinClass := ApplicationWindow
+	    ].
+	    self setupWindowFor:appWinClass new.
+	].
+	origin isPoint ifFalse:[
+	    |windowExtent newOrg|
+
+	    windowExtent := window extent.
 
-        usableHeight := window device usableHeightAt:window origin.
-        window corner y > usableHeight ifTrue:[
-            y := usableHeight - window height.
-            window origin:(window origin x @ (y max:0))
-        ].
-        "/ the following code creates a master-slave relationship, if
-        "/ the masterApplication is not nil.
-        "/ Disabled, because: the masterApplication is used to fulfill missing aspects,
-        "/ which has nothing to do with a window master-slave relationship.
-        
-"/        application masterApplication notNil ifTrue:[ 
+	    mainWin notNil ifTrue:[
+		(windowExtent x > mainWin extent x or:[windowExtent y > mainWin extent y]) ifFalse:[
+		    newOrg := mainWin bounds center - (windowExtent // 2).
+		].
+	    ].
+	    newOrg isNil ifTrue:[
+		newOrg := monitorBounds center - (windowExtent // 2).
+	    ].
+	    window origin:newOrg rounded.
+	].
+	y := window origin y.
+	x := window origin x.
+
+	window corner y > monitorBounds bottom ifTrue:[
+	    y := (monitorBounds bottom - window height) max:(monitorBounds top).
+
+	].
+	window corner x > monitorBounds right ifTrue:[
+	    x := (monitorBounds right - window width) max:(monitorBounds left).
+	].
+	window origin:(x @ y ).
+
+
+	"/ the following code creates a master-slave relationship, if
+	"/ the masterApplication is not nil.
+	"/ Disabled, because: the masterApplication is used to fulfill missing aspects,
+	"/ which has nothing to do with a window master-slave relationship.
+
+"/        application masterApplication notNil ifTrue:[
 "/            masterWindow := application masterApplication window.
 "/            (masterWindow isMaster or:[masterWindow isSlave or:[masterWindow isPartner]])
 "/            ifFalse:[
@@ -1492,22 +1536,22 @@
 "/            window beSlave.
 "/        ].
 
-        "/ must be done explicit, by passing an appropriate windowType
+	"/ must be done explicit, by passing an appropriate windowType
 
-        type = #slave ifTrue:[
-            window beSlave.
-        ].
-        type = #partner ifTrue:[
-            window bePartner.
-        ].
+	type = #slave ifTrue:[
+	    window beSlave.
+	].
+	type = #partner ifTrue:[
+	    window bePartner.
+	].
 
-        ((type = #slave or:[type = #partner]) 
-        and:[ window windowGroup isNil ])
-        ifTrue:[
-            window openInGroup:(WindowGroup activeGroup).
-        ] ifFalse:[
-            window open.
-        ].
+	((type = #slave or:[type = #partner])
+	and:[ window windowGroup isNil ])
+	ifTrue:[
+	    window openInGroup:(WindowGroup activeGroup).
+	] ifFalse:[
+	    window open.
+	].
 
 "/ the following automatism is probably too cryptic and has too much of a side effect.
 "/ I prefer to leave things as they are: i.e. enforce the programmer to
@@ -1516,12 +1560,12 @@
 "/        type = #slave ifTrue:[
 "/            window windowGroup topViews first beMaster
 "/        ].
-        ^ self
+	^ self
     ].
 
     type == #popUp ifTrue:[
-        window fixPosition:(device pointerPosition).
-        ^ window openAsPopUp.
+	window fixPosition:(device pointerPosition).
+	^ window openAsPopUp.
     ].
 
     "
@@ -1540,7 +1584,7 @@
      If there is an application, it knows best what to do"
 
     application isNil ifTrue:[
-        ^ self resources string:aString
+	^ self resources string:aString
     ].
     ^ application translateString:aString
 ! !
@@ -1548,9 +1592,9 @@
 !WindowBuilder class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview2/WindowBuilder.st,v 1.142 2010-02-05 12:30:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/WindowBuilder.st,v 1.143 2010-10-11 09:07:28 mb Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libview2/WindowBuilder.st,v 1.142 2010-02-05 12:30:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libview2/WindowBuilder.st,v 1.143 2010-10-11 09:07:28 mb Exp $'
 ! !