Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 18 Nov 2016 21:26:33 +0000
branchjv
changeset 7715 925b859e1758
parent 7714 dcf48ff796c8 (current diff)
parent 7678 46ad5aafe09e (diff)
child 7716 3dba89415c91
Merge
DeviceGraphicsContext.st
DisplayRootView.st
DisplaySurface.st
FontDescription.st
Form.st
GraphicsMedium.st
Image.st
SimpleView.st
StandardSystemView.st
SynchronousWindowSensor.st
WinWorkstation.st
WindowSensor.st
XWorkstation.st
XftFontDescription.st
--- a/Color.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/Color.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
 	      All Rights Reserved
@@ -19,9 +17,9 @@
 	instanceVariableNames:'red green blue device colorId ditherForm replacementColor
 		writable'
 	classVariableNames:'MaxValue Cells Black White LightGrey Grey DarkGrey Pseudo0
-		Pseudo1 PseudoAll Red Green Blue RetryAllocation DitherBits
-		ColorErrorSignal ColorAllocationFailSignal InvalidColorNameSignal
-		StandardColorValues Transparent'
+		Pseudo1 PseudoAll Red Green Blue Yellow Orange RetryAllocation
+		DitherBits ColorErrorSignal ColorAllocationFailSignal
+		InvalidColorNameSignal StandardColorValues Transparent'
 	poolDictionaries:''
 	category:'Graphics-Support'
 !
@@ -72,7 +70,7 @@
 
     The default algorithm for color allocation is to ask the display for colors as
     new colors are created. When running out of colors, dithered colors will be used,
-    using existing nearest colors and a dither pattern to aproximate the color.
+    using existing nearest colors and a dither pattern to approximate the color.
     There could be situations, where no good colors are available for the dither, leading
     to ugly looking dither colors.
     This can be avoided by preallocating a set of colors over the complete range, which
@@ -99,10 +97,10 @@
 
       Lobby           <Registry>      all colors in use - keeps track of already allocated
                                       colors for reuse and finalization.
-                                      (dont use it: this will be moved to the device)
+                                      (don't use it: this will be moved to the device)
 
       Cells           <Registry>      keeps track of allocated writable color cells
-                                      (dont use it: this will be moved to the device)
+                                      (don't use it: this will be moved to the device)
 
       FixColors       <Array>         preallocated colors for dithering on Display
       NumRedFix       <Integer>       number of distinct red values in FixColors
@@ -2025,7 +2023,14 @@
 orange
     "return the orange color - ST-80 compatibility"
 
-     ^ self orange:100
+    Orange isNil ifTrue:[
+        Orange := self redPercent:100 greenPercent:50 bluePercent:0.
+    ].
+    ^ Orange
+
+    "
+     Color orange inspect
+    "
 !
 
 orange: orange
@@ -2048,10 +2053,14 @@
     "return the red color"
 
     Red isNil ifTrue:[
-	Red := self redPercent:100 greenPercent:0 bluePercent:0.
+        Red := self redPercent:100 greenPercent:0 bluePercent:0.
     ].
     ^ Red
 
+    "
+     Color red inspect
+    "
+
     "Modified: 23.4.1996 / 13:29:44 / cg"
 !
 
@@ -2114,15 +2123,26 @@
     "return the white-color"
 
     White isNil ifTrue:[
-	White := self redPercent:100 greenPercent:100 bluePercent:100.
+        White := self redPercent:100 greenPercent:100 bluePercent:100.
     ].
     ^ White
+
+    "
+     Color white inspect
+    "
 !
 
 yellow
     "return the yellow color - ST-80 compatibility"
 
-    ^ self yellow:100
+    Yellow isNil ifTrue:[
+        Yellow := self redPercent:100 greenPercent:100 bluePercent:0.
+    ].
+    ^ Yellow
+
+    "
+     Color yellow inspect
+    "
 
     "Modified: 23.4.1996 / 13:33:56 / cg"
 !
@@ -4809,7 +4829,7 @@
         ]
     ].
 
-    "/ on high-resolution true-color systems, dont care for dithering and
+    "/ on high-resolution true-color systems, don't care for dithering and
     "/ especially freeing colors
     "/ (no need to register)
 
@@ -5092,9 +5112,55 @@
 !
 
 contrastingBlackOrWhite
-    "answer either black or white, whichever gives a better contrast"
-
-    ^ self brightness < 0.60 ifTrue:[self class white] ifFalse:[self class black]
+    "answer either black or white, whichever gives a better contrast
+     for drawing text on a background with my color.
+     (i.e. if I am dark, return white; if I am bright, return black"
+
+    ^ self brightness < 0.55 
+        ifTrue:[self class white] 
+        ifFalse:[self class black]
+
+    "
+     (Color blue) contrastingBlackOrWhite
+     (Color red) contrastingBlackOrWhite
+     (Color green) contrastingBlackOrWhite
+     (Color yellow) contrastingBlackOrWhite
+    "
+!
+
+contrastingColorFor:aBackgroundColor
+    "answer a slightly brightened or darkened variant of myself,
+     to ensure a good contrast when showing text on a background color.
+     i.e. when drawing read on grey, it might be better to darken or brighten 
+     the red, if its brightness is too near to the grey's brightness.
+     Use this for alert strings shown on a color background."
+
+    |colorUsed bgBrightness|
+
+    colorUsed := self.
+    bgBrightness := aBackgroundColor brightness.
+    
+    (bgBrightness dist:colorUsed brightness) < 0.5 ifTrue:[
+        bgBrightness > 0.5 ifTrue:[
+            colorUsed := self slightlyDarkened.
+            (bgBrightness dist:colorUsed brightness) < 0.5 ifTrue:[
+                colorUsed := self darkened.
+            ].
+        ] ifFalse:[
+            colorUsed := self slightlyLightened.
+            (bgBrightness dist:colorUsed brightness) < 0.5 ifTrue:[
+                colorUsed := self lightened.
+            ].
+        ].    
+    ].
+    ^ colorUsed.
+
+    "
+     (Color blue) contrastingColorFor:Color white.
+     (Color blue) contrastingColorFor:Color blue.
+     (Color red) contrastingColorFor:Color grey
+     (Color blue) contrastingColorFor:Color black
+    "
 !
 
 darkened
--- a/CompoundFont.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/CompoundFont.st	Fri Nov 18 21:26:33 2016 +0000
@@ -23,9 +23,9 @@
  OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
  SUCH DAMAGE.
 "
-
+"{ Package: 'stx:libview' }"
 
-"{ Package: 'stx:libview' }"
+"{ NameSpace: Smalltalk }"
 
 FontDescription subclass:#CompoundFont
 	instanceVariableNames:'baseFont characterToFontMapping maxAscent maxDescent maxHeight
@@ -337,8 +337,8 @@
 !
 
 isFixedWidth
-    "return true, if this is a fixed pitch font (i.e. all characters
-     are of the same width)"
+    "return true, if this is a fixed pitch font 
+     (i.e. all characters are of the same width)"
 
     |w|
 
@@ -406,5 +406,6 @@
 !CompoundFont class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/CompoundFont.st,v 1.9 2006-04-18 11:24:51 stefan Exp $'
+    ^ '$Header$'
 ! !
+
--- a/Cursor.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/Cursor.st	Fri Nov 18 21:26:33 2016 +0000
@@ -50,37 +50,37 @@
     I represents cursors in a device independent manner.
     Normally, cursors are defined at view creation time,
     via 
-	'aView cursor:aCursor'.
+        'aView cursor:aCursor'.
 
     [Instance variables:]
 
-	shape           <Symbol>        a shape (i.e. #arrow, #hand, ...) or nil
-	sourceForm      <Form>          if shape is nil, the source bits
-	maskForm        <Form>          if shape is nil, the mask bits
-	hotX            <SmallInteger>  if shape is nil, the hotSpot x of the cursor
-	hotY            <SmallInteger>  if shape is nil, the hotSpot y of the cursor
-	device          <aDevice>       the device, if associated to one
-	cursorId        <anObject>      the device-specific id if device is nonNil
+        shape           <Symbol>        a shape (i.e. #arrow, #hand, ...) or nil
+        sourceForm      <Form>          if shape is nil, the source bits
+        maskForm        <Form>          if shape is nil, the mask bits
+        hotX            <SmallInteger>  if shape is nil, the hotSpot x of the cursor
+        hotY            <SmallInteger>  if shape is nil, the hotSpot y of the cursor
+        device          <aDevice>       the device, if associated to one
+        cursorId        <anObject>      the device-specific id if device is nonNil
 
     [class variables:]
 
-	Lobby           <Registry>      keeps track of known device cursors
-					(dont use it: this will be moved to the device)
-
-	DefaultFgColor  <Color>         default foreground color for cursors (usually black)
-	DefaultBgColor  <Color>         default background color for cursors (usually white)
-
-	NormalCursor    <Cursor>        cached instance of normal (arrow) cursor
-	 ...
+        Lobby           <Registry>      keeps track of known device cursors
+                                        (don't use it: this will be moved to the device)
+
+        DefaultFgColor  <Color>         default foreground color for cursors (usually black)
+        DefaultBgColor  <Color>         default background color for cursors (usually white)
+
+        NormalCursor    <Cursor>        cached instance of normal (arrow) cursor
+         ...
 
     [see also:]
-	DeviceWorkstation 
-	DisplaySurface
-	Font Color Image Form
-	( introduction to view programming :html: programming/viewintro.html#CURSOR )
+        DeviceWorkstation 
+        DisplaySurface
+        Font Color Image Form
+        ( introduction to view programming :html: programming/viewintro.html#CURSOR )
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 "
 !
 
--- a/Depth2Image.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/Depth2Image.st	Fri Nov 18 21:26:33 2016 +0000
@@ -971,16 +971,16 @@
     "return a collection of colors used in the receiver.
      For depth2 images, we return the colorMap here, assuming all
      pixels are used ...
-     ... which is not really true - it could use not all colors"
+     ... which is not really true - not all colors need to be"
 
     (photometric == #whiteIs0 or:[photometric == #blackIs0]) ifTrue:[
-	^ Array with:(Color black)
-		with:(Color gray:33)
-		with:(Color gray:67)
-		with:(Color white).
+        ^ Array with:(Color black)
+                with:(Color gray:33)
+                with:(Color gray:67)
+                with:(Color white).
     ].
     photometric == #palette ifTrue:[
-	^ colorMap
+        ^ colorMap
     ].
     ^ super usedColors
 
@@ -993,7 +993,7 @@
      ... which is not really true"
 
     "actually, this is wrong - we have to look if those are
-     really used. However, assume that we dont care for
+     really used. However, assume that we don't care for
      those extra colors here ..."
 
     ^ #(0 1 2 3)
--- a/DeviceGraphicsContext.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/DeviceGraphicsContext.st	Fri Nov 18 21:26:33 2016 +0000
@@ -106,14 +106,14 @@
 
     device := Screen current.
     device isNil ifTrue:[
-	device := Display.
-	device isNil ifTrue:[
-	    (self class name,' [warning]: no Display') infoPrintCR.
-	    Smalltalk openDisplay.
-
-	    device := Screen current ? Display.
-	    device isNil ifTrue:[ self error:'no screen device' ]
-	].
+        device := Display.
+        device isNil ifTrue:[
+            (self class name,' [warning]: no Display') infoPrintCR.
+            Smalltalk lateOpenDisplay.
+
+            device := Screen current ? Display.
+            device isNil ifTrue:[ self error:'no screen device' ]
+        ].
     ].
     ^ self onDevice:device
 !
@@ -585,20 +585,20 @@
     |id|
 
     (aForm ~~ mask) ifTrue:[
-	mask := aForm.
-	gcId notNil ifTrue:[
-	    (mask == nil) ifTrue:[
-		device setBitmapMask:nil in:gcId
-	    ] ifFalse:[
-		mask := mask asFormOn:device.
-		id := mask id.
-		(mask depth == 1) ifTrue:[
-		    device setBitmapMask:id in:gcId
-		] ifFalse:[
-		    device setPixmapMask:id in:gcId
-		]
-	    ]
-	]
+        mask := aForm.
+        gcId notNil ifTrue:[
+            (mask == nil) ifTrue:[
+                device setBitmapMask:nil in:gcId
+            ] ifFalse:[
+                mask := mask asFormOn:device.
+                id := mask drawableId.
+                (mask depth == 1) ifTrue:[
+                    device setBitmapMask:id in:gcId
+                ] ifFalse:[
+                    device setPixmapMask:id in:gcId
+                ]
+            ]
+        ]
     ]
 !
 
@@ -743,11 +743,11 @@
 !
 
 setGraphicsExposures:aBoolean
-    "want to if aBoolean is true - or dont want to be notified
+    "want to if aBoolean is true - or don't want to be notified
      of graphics exposures"
 
     gcId notNil ifTrue:[
-	device setGraphicsExposures:aBoolean in:gcId
+        device setGraphicsExposures:aBoolean in:gcId
     ]
 !
 
@@ -1944,15 +1944,21 @@
 
     deviceForm := aForm asFormOn:device.
     deviceForm isNil ifTrue:[
-        'DeviceGraphicsContext [warning]: cannot create device-form' errorPrintCR.
+        Logger warning:'cannot create device-form'.
         ^self
     ].
-    id := deviceForm id.
-
-    id isNil ifTrue:[
-        'DeviceGraphicsContext [warning]: invalid form draw - ignored' errorPrintCR.
-        ^ self
+    id := deviceForm drawableId.
+    "temporary ..."
+    (id isNil
+     or:[aForm graphicsDevice ~~ device]) ifTrue:[
+        deviceForm := deviceForm asFormOn:device.
+        id := deviceForm drawableId.
+        id isNil ifTrue:[
+            Logger warning:'invalid form draw - ignored'.
+            ^ self
+        ].
     ].
+
     gcId isNil ifTrue:[
         self initGC
     ].
@@ -1980,7 +1986,7 @@
                     'DeviceGraphicsContext [warning]: cannot create device-mask' errorPrintCR.
                     ^self
                 ].
-                maskId := deviceMask id.
+                maskId := deviceMask drawableId.
                 maskId notNil ifTrue:[
                     deviceMask gcId isNil ifTrue:[deviceMask initGC].
                     allColor := Color allColor.
@@ -2061,7 +2067,7 @@
                             ^ self
                         ].
                         tmpForm initGC.
-                        tmpId := tmpForm id.
+                        tmpId := tmpForm drawableId.
                         tmpGCId := tmpForm gcId.
 
                         "
@@ -2369,7 +2375,7 @@
     device setFunction:#or in:gcId.
 
     device
-        copyFromPixmapId:tmpForm id
+        copyFromPixmapId:tmpForm drawableId
         x:0
         y:0
         gc:tmpForm gcId
@@ -2426,21 +2432,21 @@
      pX pY deviceDepth deviceForm map|
 
     deviceForm := aForm asFormOn:device.
-    id := deviceForm id.
+    id := deviceForm drawableId.
 
     "temporary ..."
     (id isNil
-    or:[aForm graphicsDevice ~~ device]) ifTrue:[
-	deviceForm := deviceForm asFormOn:device.
-	id := deviceForm id.
-	id isNil ifTrue:[
-	    'DeviceGraphicsContext [warning]: invalid form draw - ignored' errorPrintCR.
-	    ^ self
-	].
+     or:[aForm graphicsDevice ~~ device]) ifTrue:[
+        deviceForm := deviceForm asFormOn:device.
+        id := deviceForm drawableId.
+        id isNil ifTrue:[
+            Logger warning:'invalid form draw (opaque) - ignored'.
+            ^ self
+        ].
     ].
 
     gcId isNil ifTrue:[
-	self initGC
+        self initGC
     ].
     deviceForm gcId isNil ifTrue:[deviceForm initGC].
 
@@ -2455,30 +2461,30 @@
      and is always drawn opaque.
     "
     (aForm depth ~~ 1) ifTrue:[
-	device
-	    copyFromPixmapId:id
-	    x:0
-	    y:0
-	    gc:deviceForm gcId
-	    to:drawableId
-	    x:pX
-	    y:pY
-	    gc:gcId
-	    width:w
-	    height:h.
-	^ self
+        device
+            copyFromPixmapId:id
+            x:0
+            y:0
+            gc:deviceForm gcId
+            to:drawableId
+            x:pX
+            y:pY
+            gc:gcId
+            width:w
+            height:h.
+        ^ self
     ].
     map := aForm colorMap.
     map notNil ifTrue:[
-	paint := map at:2.
-	bgPaint := map at:1.
+        paint := map at:2.
+        bgPaint := map at:1.
     ].
 
     "/ if no bgPaint is set, this is a non-opaque draw
 
     bgPaint isNil ifTrue:[
-	self displayDeviceForm:aForm x:x y:y.
-	^ self
+        self displayDeviceForm:aForm x:x y:y.
+        ^ self
     ].
 
     "the following code is somewhat complicated, since it has to deal
@@ -2492,43 +2498,43 @@
     "
     easy := true.
     paint isColor ifFalse:[
-	easy := false
+        easy := false
     ] ifTrue:[
-	fgId := paint colorId.
-	fgId isNil ifTrue:[
-	    easy := false
-	]
+        fgId := paint colorId.
+        fgId isNil ifTrue:[
+            easy := false
+        ]
     ].
     bgPaint isColor ifFalse:[
-	easy := false
+        easy := false
     ] ifTrue:[
-	bgId := bgPaint colorId.
-	bgId isNil ifTrue:[
-	    easy := false
-	]
+        bgId := bgPaint colorId.
+        bgId isNil ifTrue:[
+            easy := false
+        ]
     ].
 
     easy ifTrue:[
-	"
-	 easy: both paint and bgPaint are real colors
-	"
-	((foreground ~~ paint) or:[background ~~ bgPaint]) ifTrue:[
-	    device setForeground:fgId background:bgId in:gcId.
-	    foreground := paint.
-	    background := bgPaint.
-	].
-	device
-	    copyPlaneFromPixmapId:id
-	    x:0
-	    y:0
-	    gc:(deviceForm gcId)
-	    to:drawableId
-	    x:pX
-	    y:pY
-	    gc:gcId
-	    width:w
-	    height:h.
-	^ self
+        "
+         easy: both paint and bgPaint are real colors
+        "
+        ((foreground ~~ paint) or:[background ~~ bgPaint]) ifTrue:[
+            device setForeground:fgId background:bgId in:gcId.
+            foreground := paint.
+            background := bgPaint.
+        ].
+        device
+            copyPlaneFromPixmapId:id
+            x:0
+            y:0
+            gc:(deviceForm gcId)
+            to:drawableId
+            x:pX
+            y:pY
+            gc:gcId
+            width:w
+            height:h.
+        ^ self
     ].
 
     "
@@ -2539,120 +2545,120 @@
     deviceDepth := device depth.
 
     (fgId notNil and:[function == #copy]) ifTrue:[
-	"
-	 only bg is dithered; fill with bg first ...
-	"
-	savedPaint := paint.
-	self paint:bgPaint.
-	self fillDeviceRectangleX:pX y:pY width:w height:h.
-	self paint:savedPaint.
-
-	"
-	 if paint color is all-0 or all-1's, we can do it in one
-	 operation ...
-	"
-	((fgId ~~ ((1 bitShift:deviceDepth)-1))
-	and:[fgId ~~ allBits]) ifTrue:[
-	    "
-	     clear fg-bits ...
-	    "
-	    device setForeground:0 background:allBits in:gcId.
-	    device setFunction:#and in:gcId.
-	    device
-		copyPlaneFromPixmapId:id
-		x:0
-		y:0
-		gc:(deviceForm gcId)
-		to:drawableId
-		x:pX
-		y:pY
-		gc:gcId
-		width:w
-		height:h
-	].
-
-	fgId ~~ 0 ifTrue:[
-	    "
-	     or-in fg-bits ...
-	    "
-	    device setForeground:fgId background:0 in:gcId.
-	    device setFunction:#or in:gcId.
-	    device
-		copyPlaneFromPixmapId:id
-		x:0
-		y:0
-		gc:(deviceForm gcId)
-		to:drawableId
-		x:pX
-		y:pY
-		gc:gcId
-		width:w
-		height:h
-	].
-	"
-	 flush foreground/background cache
-	"
-	foreground := nil.
-	background := nil.
-	device setFunction:function in:gcId.
-	^ self
+        "
+         only bg is dithered; fill with bg first ...
+        "
+        savedPaint := paint.
+        self paint:bgPaint.
+        self fillDeviceRectangleX:pX y:pY width:w height:h.
+        self paint:savedPaint.
+
+        "
+         if paint color is all-0 or all-1's, we can do it in one
+         operation ...
+        "
+        ((fgId ~~ ((1 bitShift:deviceDepth)-1))
+        and:[fgId ~~ allBits]) ifTrue:[
+            "
+             clear fg-bits ...
+            "
+            device setForeground:0 background:allBits in:gcId.
+            device setFunction:#and in:gcId.
+            device
+                copyPlaneFromPixmapId:id
+                x:0
+                y:0
+                gc:(deviceForm gcId)
+                to:drawableId
+                x:pX
+                y:pY
+                gc:gcId
+                width:w
+                height:h
+        ].
+
+        fgId ~~ 0 ifTrue:[
+            "
+             or-in fg-bits ...
+            "
+            device setForeground:fgId background:0 in:gcId.
+            device setFunction:#or in:gcId.
+            device
+                copyPlaneFromPixmapId:id
+                x:0
+                y:0
+                gc:(deviceForm gcId)
+                to:drawableId
+                x:pX
+                y:pY
+                gc:gcId
+                width:w
+                height:h
+        ].
+        "
+         flush foreground/background cache
+        "
+        foreground := nil.
+        background := nil.
+        device setFunction:function in:gcId.
+        ^ self
     ].
 
     (bgId notNil and:[function == #copy]) ifTrue:[
-	"
-	 only fg is dithered; fill with fg first ...
-	"
-	self fillDeviceRectangleX:pX y:pY width:w height:h.
-
-	"
-	 if paint color is all-0 or all-1's, we can do it in one
-	 operation ...
-	"
-	((bgId ~~ ((1 bitShift:deviceDepth)-1))
-	and:[bgId ~~ allBits]) ifTrue:[
-	    "
-	     clear bg-bits ...
-	    "
-	    device setForeground:allBits background:0 in:gcId.
-	    device setFunction:#and in:gcId.
-	    device
-		copyPlaneFromPixmapId:id
-		x:0
-		y:0
-		gc:(deviceForm gcId)
-		to:drawableId
-		x:pX
-		y:pY
-		gc:gcId
-		width:w
-		height:h
-	].
-
-	"
-	 or-in bg-bits ...
-	"
-	bgId ~~ 0 ifTrue:[
-	    device setForeground:0 background:bgId in:gcId.
-	    device setFunction:#or in:gcId.
-	    device
-		copyPlaneFromPixmapId:id
-		x:0
-		y:0
-		gc:(deviceForm gcId)
-		to:drawableId
-		x:pX
-		y:pY
-		gc:gcId
-		width:w
-		height:h
-	].
-	"
-	 flush foreground/background cache
-	"
-	foreground := nil.
-	background := nil.
-	device setFunction:function in:gcId.
-	^ self
+        "
+         only fg is dithered; fill with fg first ...
+        "
+        self fillDeviceRectangleX:pX y:pY width:w height:h.
+
+        "
+         if paint color is all-0 or all-1's, we can do it in one
+         operation ...
+        "
+        ((bgId ~~ ((1 bitShift:deviceDepth)-1))
+        and:[bgId ~~ allBits]) ifTrue:[
+            "
+             clear bg-bits ...
+            "
+            device setForeground:allBits background:0 in:gcId.
+            device setFunction:#and in:gcId.
+            device
+                copyPlaneFromPixmapId:id
+                x:0
+                y:0
+                gc:(deviceForm gcId)
+                to:drawableId
+                x:pX
+                y:pY
+                gc:gcId
+                width:w
+                height:h
+        ].
+
+        "
+         or-in bg-bits ...
+        "
+        bgId ~~ 0 ifTrue:[
+            device setForeground:0 background:bgId in:gcId.
+            device setFunction:#or in:gcId.
+            device
+                copyPlaneFromPixmapId:id
+                x:0
+                y:0
+                gc:(deviceForm gcId)
+                to:drawableId
+                x:pX
+                y:pY
+                gc:gcId
+                width:w
+                height:h
+        ].
+        "
+         flush foreground/background cache
+        "
+        foreground := nil.
+        background := nil.
+        device setFunction:function in:gcId.
+        ^ self
     ].
 
     "
@@ -2672,8 +2678,8 @@
     "
     dx := dy := 0.
     maskOrigin notNil ifTrue:[
-	dx := maskOrigin x.
-	dy := maskOrigin y
+        dx := maskOrigin x.
+        dy := maskOrigin y
     ].
 
     bgForm paint:bgPaint.
@@ -2716,16 +2722,16 @@
     "
     device setForeground:0 background:allBits in:gcId.
     device
-	copyFromPixmapId:tmpForm id
-	x:0
-	y:0
-	gc:tmpForm gcId
-	to:drawableId
-	x:pX
-	y:pY
-	gc:gcId
-	width:w
-	height:h.
+        copyFromPixmapId:tmpForm drawableId
+        x:0
+        y:0
+        gc:tmpForm gcId
+        to:drawableId
+        x:pX
+        y:pY
+        gc:gcId
+        width:w
+        height:h.
 
     "
      release tempForms immediately
@@ -2929,10 +2935,10 @@
         mask notNil ifTrue:[
             "/ draw fg dithered
             (mask depth == 1) ifTrue:[
-                device setBitmapMask:mask id in:gcId.
+                device setBitmapMask:mask drawableId in:gcId.
                 device setForegroundColor:foreground backgroundColor:background in:gcId.
             ] ifFalse:[
-                device setPixmapMask:mask id in:gcId
+                device setPixmapMask:mask drawableId in:gcId
             ].
         ].
 
@@ -3007,7 +3013,7 @@
     "
     device setForeground:0 background:allBits in:gcId.
     device
-        copyFromId:tmpForm id
+        copyFromId:tmpForm drawableId
         x:0 y:0 gc:tmpForm gcId
         to:drawableId
         x:pX y:(pY-ascent) gc:gcId
@@ -3564,9 +3570,9 @@
 
     mask notNil ifTrue:[
         (mask depth == 1) ifTrue:[
-            device setBitmapMask:(mask id) in:gcId
+            device setBitmapMask:(mask drawableId) in:gcId
         ] ifFalse:[
-            device setPixmapMask:(mask id) in:gcId
+            device setPixmapMask:(mask drawableId) in:gcId
         ].
         maskOrigin notNil ifTrue:[
             device setMaskOriginX:maskOrigin x y:maskOrigin y in:gcId
@@ -3899,7 +3905,7 @@
 
     drawableType := #window.
     container := aView container.
-    container notNil ifTrue:[ parentId := container id ].
+    container notNil ifTrue:[ parentId := container drawableId].
     device registerGraphicsContext:self.    "this is a registerChange:"
 ! !
 
@@ -3962,7 +3968,7 @@
     "set the windows border shape"
 
     drawableId notNil ifTrue:[
-	device setWindowBorderShape:(aForm id) in:drawableId
+        device setWindowBorderShape:(aForm drawableId) in:drawableId
     ].
 !
 
@@ -3990,7 +3996,7 @@
      X shape extension."
 
     drawableId notNil ifTrue:[
-	^ device setWindowShape:(aForm id) in:drawableId
+        ^ device setWindowShape:(aForm drawableId) in:drawableId
     ].
     ^ false.
 ! !
--- a/DeviceWorkstation.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/DeviceWorkstation.st	Fri Nov 18 21:26:33 2016 +0000
@@ -815,27 +815,27 @@
 
     "/
     "/ if there is only one screen,
-    "/ take that ... it ought to be display
+    "/ take that ... it ought to be the Display
     "/
     AllScreens size <= 1 ifTrue:[
-	LastActiveProcess := LastActiveScreen := nil.
-	Display notNil ifTrue:[
-	    ^ Display
-	]
+        LastActiveProcess := LastActiveScreen := nil.
+        Display notNil ifTrue:[
+            ^ Display
+        ]
     ].
 
     "/
     "/ someone willing to tell me ?
     "/
     (dev := self currentScreenQuerySignal query) notNil ifTrue:[
-	^ dev
+        ^ dev
     ].
 
     thisProcess := Processor activeProcess.
     LastActiveScreen notNil ifTrue:[
-	LastActiveProcess == thisProcess ifTrue:[
-	    ^ LastActiveScreen
-	]
+        LastActiveProcess == thisProcess ifTrue:[
+            ^ LastActiveScreen
+        ]
     ].
 
     "/
@@ -845,14 +845,14 @@
     "/ the current windowGroup got corrupted somehow ...
 
     (wg := WindowGroup activeGroup) notNil ifTrue:[
-	"/
-	"/ ok, not a background process or scheduler ...
-	"/
-	(dev := wg graphicsDevice) notNil ifTrue:[
-	    LastActiveScreen := dev.
-	    LastActiveProcess := thisProcess.
-	    ^ dev
-	].
+        "/
+        "/ ok, not a background process or scheduler ...
+        "/
+        (dev := wg graphicsDevice) notNil ifTrue:[
+            LastActiveScreen := dev.
+            LastActiveProcess := thisProcess.
+            ^ dev
+        ].
     ].
 
     "/
@@ -861,6 +861,9 @@
     "/
 "/    'DevWorkstation [info]: cannot figure out current screen - use default' infoPrintCR.
 
+    Display isNil ifTrue:[
+        'DevWorkstation [info]: Display is nil.' infoPrintCR.
+    ].    
     ^ Display
 
     "
@@ -1574,22 +1577,22 @@
     w2 := window2 ? self rootView.
 
     (w1 device ~~ self or:[w2 device ~~ self]) ifTrue:[
-	self error:'Huh - Cross device translation' mayProceed:true.
-	^ aPoint
+        self error:'Huh - Cross device translation' mayProceed:true.
+        ^ aPoint
     ].
     w1 isView ifTrue:[
-	offset1 := 0
+        offset1 := 0
     ] ifFalse:[
-	offset1 := w1 origin.
-	w1 := w1 container.
+        offset1 := w1 origin.
+        w1 := w1 container.
     ].
     w2 isView ifTrue:[
-	offset2 := 0
+        offset2 := 0
     ] ifFalse:[
-	offset2 := w2 origin.
-	w2 := w2 container.
-    ].
-    devicePoint := self translatePoint:aPoint from:(w1 id) to:(w2 id).
+        offset2 := w2 origin.
+        w2 := w2 container.
+    ].
+    devicePoint := self translatePoint:aPoint from:(w1 drawableId) to:(w2 drawableId).
     devicePoint isNil ifTrue:[ ^ aPoint].
     ^ devicePoint + offset1 - offset2
 
@@ -2001,7 +2004,7 @@
 !
 
 hasColors:aBoolean
-    "set the hasColors flag - needed since some servers dont tell the
+    "set the hasColors flag - needed since some servers don't tell the
      truth if a monochrome monitor is connected to a color server.
      Clearing the hasColors flag in the rc file will force use of grey
      colors (which might make a difference, since some colors are hard to
@@ -2673,16 +2676,30 @@
     "return the number of horizontal pixels per inch of the display"
 
     ^ (width / widthMM) * 25.4
+
+    "
+     Display horizontalPixelPerInch
+     Display widthInMillimeter:(Display width * 25.4) / 120
+     Display heightInMillimeter:(Display height * 25.4) / 120
+    "
 !
 
 horizontalPixelPerMillimeter
     "return the number of horizontal pixels per millimeter of the display"
 
     resolutionHor notNil ifTrue:[
-	^ resolutionHor
+        ^ resolutionHor
     ].
     resolutionHor := (width / widthMM) asFloat.
     ^ resolutionHor
+
+    "
+     Display horizontalPixelPerMillimeter
+     Display verticalPixelPerMillimeter
+     Display width
+     Display widthInMillimeter
+     Display heightInMillimeter
+    "
 !
 
 pixelPerInch
@@ -3373,9 +3390,9 @@
     self rememberCopyBuffer.
     self setCopyBuffer:something.
 
-    viewID := aView id.
+    viewID := aView drawableId.
     viewID notNil ifTrue:[ "/ if the view is not already closed
-	self setClipboardObject:something owner:viewID.
+        self setClipboardObject:something owner:viewID.
     ]
 !
 
@@ -3401,16 +3418,16 @@
 
     s := aString ? ''.
     s isString ifFalse:[
-	s := s asStringWithCRsFrom:1 to:(s size) compressTabs:false withCR:false
-    ].
-
-    viewID := aView id.
+        s := s asStringWithCRsFrom:1 to:(s size) compressTabs:false withCR:false
+    ].
+
+    viewID := aView drawableId.
     viewID notNil ifTrue:[ "/ if the view is not already closed
-	"/ TODO: should add support to pass emphasis information too
-	s := s string.
-	self setClipboardText:s owner:viewID.
+        "/ TODO: should add support to pass emphasis information too
+        s := s string.
+        self setClipboardText:s owner:viewID.
     ] ifFalse:[
-	Transcript showCR:'DeviceWorkstation [warning]: setClipboardText - view has no id; selection only kept locally'
+        Transcript showCR:'DeviceWorkstation [warning]: setClipboardText - view has no id; selection only kept locally'
     ].
 !
 
@@ -3551,13 +3568,13 @@
 colorNamed:aString
     "allocate a color with color name - return the color index (i.e. colorID).
      Only a subset of the colorNames are available on all displays;
-     therefore, dont use this method; at least only for the common names such as red, green, blue etc."
+     therefore, don't use this method; at least only for the common names such as red, green, blue etc."
 
     ^ self
-	getScaledRGBFromName:aString
-	into:[:r :g :b |
-	    self colorScaledRed:r scaledGreen:g scaledBlue:b
-	]
+        getScaledRGBFromName:aString
+        into:[:r :g :b |
+            self colorScaledRed:r scaledGreen:g scaledBlue:b
+        ]
 
     "
      Screen current colorNamed:'red'
@@ -5658,12 +5675,12 @@
      Return true if ok, false if it failed for some reason."
 
     activeKeyboardGrab notNil ifTrue:[
-	self ungrabKeyboard.
-	activeKeyboardGrab := nil
-    ].
-    (self grabKeyboardIn:(aView id)) ifTrue:[
-	activeKeyboardGrab := aView.
-	^ true
+        self ungrabKeyboard.
+        activeKeyboardGrab := nil
+    ].
+    (self grabKeyboardIn:(aView drawableId)) ifTrue:[
+        activeKeyboardGrab := aView.
+        ^ true
     ].
     ^ false
 !
@@ -5704,20 +5721,20 @@
     |cId vId ok|
 
     activePointerGrab notNil ifTrue:[
-	self ungrabPointer.
-	activePointerGrab := nil
-    ].
-    vId := aView id.
+        self ungrabPointer.
+        activePointerGrab := nil
+    ].
+    vId := aView drawableId.
     aCursorOrNil notNil ifTrue:[
-	cId := aCursorOrNil id.
-	ok := self grabPointerIn:vId withCursorId:cId.
+        cId := aCursorOrNil id.
+        ok := self grabPointerIn:vId withCursorId:cId.
     ] ifFalse:[
-	ok := self grabPointerIn:vId.
+        ok := self grabPointerIn:vId.
     ].
 
     ok ifTrue:[
-	activePointerGrab := aView.
-	^ true
+        activePointerGrab := aView.
+        ^ true
     ].
     ^ false
 !
@@ -6011,13 +6028,16 @@
 
     self releaseDeviceResources.
     self closeConnection.
+    self == Display ifTrue:[
+        Display := nil.
+    ].    
     dispatching ifTrue:[
-	Logger info:'finished dispatch (close): %1' with:self.
-	dispatching := false.
+        Logger info:'finished dispatch (close): %1' with:self.
+        dispatching := false.
     ].
     dispatchProcess notNil ifTrue:[
-	dispatchProcess terminate.
-    ].
+        dispatchProcess terminate.
+    ].    
 
     "Modified: 13.1.1997 / 22:13:18 / cg"
 !
@@ -6358,42 +6378,42 @@
     root foreground:blackColor background:whiteColor.
 
     root xoring:[
-	|left right top bottom newOrigin newCorner p|
-
-	rect := origin extent:extent.
-	root displayRectangle:rect.
-
-	prevGrab := activePointerGrab.
-	self grabPointerInView:root withCursor:curs.
-
-	[self leftButtonPressed] whileTrue:[
-	    newOrigin := self pointerPosition.
-
-	    (newOrigin ~= origin) ifTrue:[
-		root displayRectangle:rect.
-
-		self
-		    grabPointerIn:root id
-		    withCursor:curs id
-		    pointerMode:#async
-		    keyboardMode:#sync
-		    confineTo:nil.
-
-		rect := newOrigin extent:extent.
-		root displayRectangle:rect.
-		self disposeButtonEventsFor:nil.
-		self flush.
-		origin := newOrigin.
-	    ] ifFalse:[
-		Delay waitForSeconds:0.05
-	    ]
-	].
-	root displayRectangle:rect.
+        |left right top bottom newOrigin newCorner p|
+
+        rect := origin extent:extent.
+        root displayRectangle:rect.
+
+        prevGrab := activePointerGrab.
+        self grabPointerInView:root withCursor:curs.
+
+        [self leftButtonPressed] whileTrue:[
+            newOrigin := self pointerPosition.
+
+            (newOrigin ~= origin) ifTrue:[
+                root displayRectangle:rect.
+
+                self
+                    grabPointerIn:root drawableId
+                    withCursor:curs id
+                    pointerMode:#async
+                    keyboardMode:#sync
+                    confineTo:nil.
+
+                rect := newOrigin extent:extent.
+                root displayRectangle:rect.
+                self disposeButtonEventsFor:nil.
+                self flush.
+                origin := newOrigin.
+            ] ifFalse:[
+                Delay waitForSeconds:0.05
+            ]
+        ].
+        root displayRectangle:rect.
     ].
 
     self ungrabPointer.
     prevGrab notNil ifTrue:[
-	self grabPointerInView:prevGrab.
+        self grabPointerInView:prevGrab.
     ].
 
     "flush all events pending on my display"
@@ -7066,7 +7086,7 @@
 
 leftShiftDown
     "return true, if the left shift-key is currently pressed.
-     Here, we dont differentiate between left and right shift keys."
+     Here, we don't differentiate between left and right shift keys."
 
     ^ shiftDown
 
@@ -7089,7 +7109,7 @@
 
 rightShiftDown
     "return true, if the right shift-key is currently pressed.
-     Here, we dont differentiate between left and right shift keys."
+     Here, we don't differentiate between left and right shift keys."
 
     ^ shiftDown
 
@@ -7430,7 +7450,7 @@
 setPointerPosition:newPosition
     "change the pointer position in root-window coordinates."
 
-    self setPointerPosition:newPosition in:(self rootView id)
+    self setPointerPosition:newPosition in:(self rootView drawableId)
 
     "
      Display setPointerPosition:10@30
@@ -7846,14 +7866,14 @@
      This undoes the effect of #setCursors:"
 
     self allViewsDo:[:aView |
-	|c vid cid|
-
-	(vid := aView id) notNil ifTrue:[
-	    c := aView cursor.
-	    (c notNil and:[(cid := c id) notNil]) ifTrue:[
-		self setCursor:cid in:vid
-	    ]
-	]
+        |c vid cid|
+
+        (vid := aView drawableId) notNil ifTrue:[
+            c := aView cursor.
+            (c notNil and:[(cid := c id) notNil]) ifTrue:[
+                self setCursor:cid in:vid
+            ]
+        ]
     ].
     self flush.
 
--- a/DisplayRootView.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/DisplayRootView.st	Fri Nov 18 21:26:33 2016 +0000
@@ -134,7 +134,7 @@
     "return my uuid - always the same here.
      TODO: think what happens with multiple screens..."
 
-    ^ UUID readFrom:'31be9300-41fc-11dd-b99f-001558137da0'  "/ do not change - ask cg if you dont know why
+    ^ UUID readFrom:'31be9300-41fc-11dd-b99f-001558137da0'  "/ do not change - ask cg if you don't know why
 ! !
 
 !DisplayRootView methodsFor:'destroying'!
@@ -148,6 +148,10 @@
 
 !DisplayRootView methodsFor:'dummy'!
 
+keyboardZoom:larger
+    "/ MUST be ignored here
+!
+
 redrawX:x y:y width:width height:height
     "ignored"
 ! !
--- a/DisplaySurface.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/DisplaySurface.st	Fri Nov 18 21:26:33 2016 +0000
@@ -227,121 +227,121 @@
      pixmapDepth deviceDepth defBG|
 
     self drawableId notNil ifTrue:[
-	viewBackground isColor ifTrue:[
+        viewBackground isColor ifTrue:[
 	    viewBackground := viewBackground onDevice:device.
-	    id := viewBackground colorId.
-	    "
-	     a real color (i.e. one supported by the device) ?
-	    "
-	    id notNil ifTrue:[
+            id := viewBackground colorId.
+            "
+             a real color (i.e. one supported by the device) ?
+            "
+            id notNil ifTrue:[
 		device setWindowBackground:id in:self drawableId.
-		^ self
-	    ].
-	    "
-	     no, a dithered one - must have a dither-pattern
-	     (which is ready for the device, since viewBackground
-	      is already assigned to the device)
-	    "
-	    bgPixmap := viewBackground ditherForm.
-	] ifFalse:[
-	    viewBackground notNil ifTrue:[
-		viewBackground isViewBackground ifTrue:[
-		    ^ self.
-		].
-
-		"
-		 assume, it can convert itself to a form
-		"
+                ^ self
+            ].
+            "
+             no, a dithered one - must have a dither-pattern
+             (which is ready for the device, since viewBackground
+              is already assigned to the device)
+            "
+            bgPixmap := viewBackground ditherForm.
+        ] ifFalse:[
+            viewBackground notNil ifTrue:[
+                viewBackground isViewBackground ifTrue:[
+                    ^ self.
+                ].
+
+                "
+                 assume, it can convert itself to a form
+                "
 		bgPixmap := viewBackground asFormOn:device.
-		bgPixmap isNil ifTrue:[
-		    "/ assume it knows how to draw itself
-		    ^ self
-		].
-	    ].
-	].
-
-	"
-	 must now have:
-	 a dithered color or bitmap or pixmap
-	"
-	bgPixmap isNil ifTrue:[
-	    'DisplaySurface [warning]: background not convertable - ignored' errorPrintCR.
-	    ^ self
-	].
-
-	"/ if the device does not support background pixmaps,
-	"/ set the backgroundColor to the default background.
-	"/ this will avoid flicker in win32 systems,
-	"/ since that background is drawn directly in the
-	"/ devices expose event handling.
-	"/ (in contrast, the pixmap filling is done by the
-	"/ window itself in its expose event handler)
+                bgPixmap isNil ifTrue:[
+                    "/ assume it knows how to draw itself
+                    ^ self
+                ].
+            ].
+        ].
+
+        "
+         must now have:
+         a dithered color or bitmap or pixmap
+        "
+        bgPixmap isNil ifTrue:[
+            'DisplaySurface [warning]: background not convertable - ignored' errorPrintCR.
+            ^ self
+        ].
+
+        "/ if the device does not support background pixmaps,
+        "/ set the backgroundColor to the default background.
+        "/ this will avoid flicker in win32 systems,
+        "/ since that background is drawn directly in the
+        "/ devices expose event handling.
+        "/ (in contrast, the pixmap filling is done by the
+        "/ window itself in its expose event handler)
 
 	(device supportsViewBackgroundPixmap:bgPixmap) ifFalse:[
-	    defBG := View defaultViewBackgroundColor.
-	    defBG isColor ifTrue:[
+            defBG := View defaultViewBackgroundColor.
+            defBG isColor ifTrue:[
 		defBG := defBG onDevice:device.
-		id := defBG colorId.
-		id notNil ifTrue:[
+                id := defBG colorId.
+                id notNil ifTrue:[
 		    device setWindowBackground:id in:self drawableId.
-		].
-	    ].
-	    ^ self
-	].
-
-	w := bgPixmap width.
-	h := bgPixmap height.
-
-	deviceDepth := self depth.
-	pixmapDepth := bgPixmap depth.
-
-	(pixmapDepth ~~ deviceDepth) ifTrue:[
-	    (pixmapDepth ~~ 1) ifTrue:[
-		'DisplaySurface [warning]: Bad dither depth (must be one or devices depth)' errorPrintCR.
-		^ self
-	    ].
-
-	    "
-	     convert it into a deep form
-	    "
-	    colorMap := bgPixmap colorMap.
+                ].
+            ].
+            ^ self
+        ].
+
+        w := bgPixmap width.
+        h := bgPixmap height.
+
+        deviceDepth := self depth.
+        pixmapDepth := bgPixmap depth.
+
+        (pixmapDepth ~~ deviceDepth) ifTrue:[
+            (pixmapDepth ~~ 1) ifTrue:[
+                'DisplaySurface [warning]: Bad dither depth (must be one or devices depth)' errorPrintCR.
+                ^ self
+            ].
+
+            "
+             convert it into a deep form
+            "
+            colorMap := bgPixmap colorMap.
 	    devBgPixmap := Form width:w height:h depth:deviceDepth onDevice:device.
-	    devBgPixmap isNil ifTrue:[
-		'DisplaySurface [warning]: could not create a device form for viewBackground' infoPrintCR.
-		^ self
-	    ].
-	    devBgPixmap paint:(colorMap at:1).
-	    devBgPixmap fillRectangleX:0 y:0 width:w height:h.
-	    devBgPixmap foreground:(colorMap at:2) background:(colorMap at:1).
-	    devBgPixmap copyPlaneFrom:bgPixmap x:0 y:0 toX:0 y:0 width:w height:h.
-	    bgPixmap := devBgPixmap.
-	] ifFalse:[
-	    (pixmapDepth == 1) ifTrue:[
-		"
-		 although depth matches,
-		 values in the dither are to be interpreted via the ditherForms
-		 colormap, which is not always the same as blackpixel/whitepixel ...
-		"
-		colorMap := bgPixmap colorMap.
+            devBgPixmap isNil ifTrue:[
+                'DisplaySurface [warning]: could not create a device form for viewBackground' infoPrintCR.
+                ^ self
+            ].
+            devBgPixmap paint:(colorMap at:1).
+            devBgPixmap fillRectangleX:0 y:0 width:w height:h.
+            devBgPixmap foreground:(colorMap at:2) background:(colorMap at:1).
+            devBgPixmap copyPlaneFrom:bgPixmap x:0 y:0 toX:0 y:0 width:w height:h.
+            bgPixmap := devBgPixmap.
+        ] ifFalse:[
+            (pixmapDepth == 1) ifTrue:[
+                "
+                 although depth matches,
+                 values in the dither are to be interpreted via the ditherForms
+                 colormap, which is not always the same as blackpixel/whitepixel ...
+                "
+                colorMap := bgPixmap colorMap.
 		(colorMap at:1) colorId == device whitepixel ifTrue:[
 		    (colorMap at:2) colorId == device blackpixel ifTrue:[
-			"
-			 ok, can use it
-			"
+                        "
+                         ok, can use it
+                        "
 			device setWindowBackgroundPixmap:(bgPixmap id) in:self drawableId.
-			^ self
-		    ]
-		].
-
-		"
-		 no, must invert it
-		"
+                        ^ self
+                    ]
+                ].
+
+                "
+                 no, must invert it
+                "
 		devBgPixmap := Form width:w height:h depth:deviceDepth onDevice:device.
-		devBgPixmap paint:(colorMap at:2) on:(colorMap at:1).
-		devBgPixmap copyPlaneFrom:bgPixmap x:0 y:0 toX:0 y:0 width:w height:h.
-		bgPixmap := devBgPixmap.
-	    ]
-	].
+                devBgPixmap paint:(colorMap at:2) on:(colorMap at:1).
+                devBgPixmap copyPlaneFrom:bgPixmap x:0 y:0 toX:0 y:0 width:w height:h.
+                bgPixmap := devBgPixmap.
+            ]
+        ].
 	device setWindowBackgroundPixmap:(bgPixmap id) in:self drawableId.
     ]
 
@@ -2271,7 +2271,7 @@
     device notNil ifTrue:[
         eventMask := device defaultEventMask.
     ].
-    viewBackground := gc background.
+    gc notNil ifTrue:[ viewBackground := gc background].
     backed := false.
     flags := 0.
     self initCursor
@@ -2360,7 +2360,7 @@
 
 buttonReleaseEventPending
     "return true, if a button release event is pending.
-     Dont use it, since it does not honor the windowGroup, but
+     Don't use it, since it does not honor the windowGroup, but
      goes directly to the device instead.
      Actually, its a historical leftover"
 
@@ -2438,7 +2438,7 @@
 
 heightOfContents
     "return the height of the contents in pixels.
-     Since we dont know here, just return the views size.
+     Since we don't know here, just return the views size.
      This will make your scrollbars show 100%-visible.
      Must be redefined in subviews to make scrollbars really work."
 
@@ -2447,7 +2447,7 @@
 
 widthOfContents
     "return the width of the contents in pixels.
-     Since we dont know here, just return the views size.
+     Since we don't know here, just return the views size.
      This will make your scrollbars show 100%-visible.
      Must be redefined in subviews to make scrollbars really work."
 
@@ -2456,7 +2456,7 @@
 
 xOriginOfContents
     "return the x-origin of the contents in pixels.
-     Since we dont know here, just return 0 for left.
+     Since we don't know here, just return 0 for left.
      Must be redefined in subviews to make scrollbars really work."
 
     ^ 0
@@ -2464,7 +2464,7 @@
 
 yOriginOfContents
     "return the y-origin of the contents in pixels.
-     Since we dont know here, just return 0 for top.
+     Since we don't know here, just return 0 for top.
      Must be redefined in subviews to make scrollbars really work."
 
     ^ 0
--- a/Font.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/Font.st	Fri Nov 18 21:26:33 2016 +0000
@@ -441,10 +441,17 @@
      myself on aDevice. This does NOT try to look for existing
      or replacement fonts (i.e. can be used to get physical fonts)."
 
-    |id|
+    |id xftFont|
 
     "receiver was not associated - do it now"
     device isNil ifTrue:[
+        (aDevice supportsXftFonts 
+        and:[ UserPreferences current useXFontsOnly not ]) ifTrue:[
+            xftFont := (XftFontDescription for:self) onDevice:aDevice ifAbsent:[nil].
+            xftFont notNil ifTrue:[^ xftFont].
+            UserPreferences current useXftFontsOnly ifTrue:[^ nil].
+        ].    
+        
         "ask that device for the font"
         id := aDevice 
                 getFontWithFamily:family 
--- a/FontDescription.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/FontDescription.st	Fri Nov 18 21:26:33 2016 +0000
@@ -16,11 +16,11 @@
 Object subclass:#FontDescription
 	instanceVariableNames:'family face style size encoding manufacturer name flags masks
 		sizeUnit pixelSize weight slant'
-	classVariableNames:'BoldnessMask FixedFlag ItalicFlag OutlineFlag SerifFlag
-		ShadowFlag StrikeoutFlag UnderlineFlag GenericFlag GenericFonts
-		CharacterSetToFontMapping CharacterEncodingToCharacterSetMapping
-		IsTrueTypeFlag OverlappingCharactersFlag DefaultEncoding
-		AntialiasedFlag ScalableFlag DecorativeFlag'
+	classVariableNames:'AntialiasedFlag BoldnessMask
+		CharacterEncodingToCharacterSetMapping CharacterSetToFontMapping
+		DecorativeFlag DefaultEncoding FixedFlag GenericFlag GenericFonts
+		IsTrueTypeFlag ItalicFlag OutlineFlag OverlappingCharactersFlag
+		ScalableFlag SerifFlag ShadowFlag StrikeoutFlag UnderlineFlag'
 	poolDictionaries:''
 	category:'Graphics-Support'
 !
@@ -1352,7 +1352,14 @@
      myself on aDevice. This does NOT try to look for existing
      or replacement fonts (i.e. can be used to get physical fonts)."
 
-    |newFont id|
+    |newFont id xftFont|
+
+    (aDevice supportsXftFonts 
+    and:[ UserPreferences current useXFontsOnly not ]) ifTrue:[
+        xftFont := (XftFontDescription for:self) onDevice:aDevice ifAbsent:[nil].
+        xftFont notNil ifTrue:[^ xftFont].
+        UserPreferences current useXftFontsOnly ifTrue:[^ nil].
+    ].    
 
     "ask that device for the font"
     id := aDevice 
@@ -1604,8 +1611,9 @@
 !
 
 isFixedWidth
-    "return true, if this is a fixed pitch font (i.e. all characters
-     are of the same width)"
+    "return true, if this is a fixed pitch font 
+     (i.e. all characters are of the same width).
+     Also called monospaced fonts"
 
     self subclassResponsibility
 !
@@ -1753,6 +1761,12 @@
     ^ (flags ? 0) bitTest:AntialiasedFlag
 !
 
+isDecorativeFont
+    "answer true, if this is an decorative font (currently Xft only)"
+    
+    ^ (flags ? 0) bitTest:DecorativeFlag
+!
+
 isGenericFont
     "answer true, if this is a pseudo font"
     
--- a/Form.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/Form.st	Fri Nov 18 21:26:33 2016 +0000
@@ -514,58 +514,6 @@
     ^ nil
 ! !
 
-!Form class methodsFor:'fileIn/Out'!
-
-fromFile:filename
-    "create a new form taking the bits from a file on the default device.
-     WARNING:
-     Please do no longer use this, since it will not work
-     correctly in multi-display applications (creates the form on the
-     default Display).
-     Use #fromFile:on: and pass the device as argument."
-
-    <resource:#obsolete>
-
-    self obsoleteMethodWarning:'please use Image>>fromFile:'.
-    ^ self fromFile:filename on:Screen current
-
-    "Modified: 19.12.1996 / 13:59:09 / cg"
-!
-
-fromFile:filename resolution:dpi
-    "create a new form taking the bits from a file on the default device
-     the data in the file is assumed to be for dpi resolution;
-     if it is different from the displays resolution, magnify or
-     shrink the picture (but only in integer magnification steps).
-     WARNING:
-     Please do no longer use this, since it will not work
-     correctly in multi-display applications (creates the form on the
-     default Display).
-     Use #fromFile:resolution:on: and pass the device as argument."
-
-    <resource:#obsolete>
-
-    self obsoleteMethodWarning:'please use Image>>fromFile:'.
-    ^ (self onDevice:Screen current) readFromFile:filename resolution:dpi
-
-    "Modified: 5.6.1997 / 21:06:03 / cg"
-!
-
-fromFile:filename resolution:dpi on:aDevice
-    "create a new form on device, aDevice and
-     initialize the pixels from the file filename;
-     the data in the file is assumed to be for dpi resolution;
-     if it is different from the displays resolution, magnify or
-     shrink the picture (but only in integer magnification steps)"
-
-    <resource:#obsolete>
-
-    self obsoleteMethodWarning:'please use Image>>fromFile:'.
-    ^ (self onDevice:aDevice) readFromFile:filename resolution:dpi
-
-    "Modified: 5.6.1997 / 21:05:54 / cg"
-! !
-
 !Form class methodsFor:'obsolete instance creation'!
 
 darkGreyFormOn:aDevice
@@ -1312,7 +1260,7 @@
         "/ 'Form [info]: create from data' printCR.
         ^ self class width:width height:height fromArray:data onDevice:aDevice
     ].
-    'Form [warning]: no bit data in #onDevice: - returning a black form.' infoPrintCR.
+    Logger warning:'no bit data in #onDevice: - returning a black form'.
     ^ (self class width:width height:height onDevice:aDevice) clear
 
     "Modified: / 27.7.1998 / 20:05:20 / cg"
--- a/GLXWorkstation.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/GLXWorkstation.st	Fri Nov 18 21:26:33 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libview' }"
 
+"{ NameSpace: Smalltalk }"
+
 XWorkstation subclass:#GLXWorkstation
 	instanceVariableNames:'activeWindow hasStereoExtension glOK'
 	classVariableNames:'ForceGL'
@@ -1253,7 +1255,7 @@
 
     There might be some confusion in the v3[sifd] functions: basically they
     all do the same, and could be mapped onto one st-method (such as vertex3).
-    However, the C-functions expect different argument types - I dont know if
+    However, the C-functions expect different argument types - I don't know if
     one or another of these functions suffers from any performance penalties.
     Therefore, I leave the direct 1-to-1 mapping; GL experts might know more
     about this (I use v3f in all of my code).
@@ -1270,8 +1272,8 @@
      class should be written)
 
     [author:]
-	Claus Gittinger
-	Jeff McAffer
+        Claus Gittinger
+        Jeff McAffer
 "
 ! !
 
@@ -1822,7 +1824,7 @@
 
 glxColor:index in:aGLXWindowId
     "set the drawing color;
-     for non gouraud shading, we dont care if the argument is integer or float;
+     for non gouraud shading, we don't care if the argument is integer or float;
      otherwise, better results are expected with float values."
 
 %{  /* NOCONTEXT */
@@ -1831,12 +1833,12 @@
 #ifdef OPENGL
 #else
     if (__isSmallInteger(index)) {
-	color((Colorindex)(__intVal(index)));
-	RETURN (self);
+        color((Colorindex)(__intVal(index)));
+        RETURN (self);
     }
     if (__isFloat(index)) {
-	colorf((float)(_floatVal(index)));
-	RETURN (self);
+        colorf((float)(_floatVal(index)));
+        RETURN (self);
     }
 #endif
 %}
@@ -3258,7 +3260,7 @@
 glxGconfigIn:aGLXWindowId
     "must be sent after RGBmode, doubleBuffer etc. to have these
      changes really take effect. See GLX manual.
-     (Actually, it seems to be not allowed - I dont really know)"
+     (Actually, it seems to be not allowed - I don't really know)"
 
 %{  /* NOCONTEXT */
     SETWIN(aGLXWindowId)
@@ -8831,3 +8833,4 @@
 version_CVS
     ^ '$Header$'
 ! !
+
--- a/GraphicsMedium.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/GraphicsMedium.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -39,16 +41,16 @@
 documentation
 "
     this is an abstract superclass for all kinds of drawables which
-    have a physical representation (i.e. have an extent). Dont use messages
-    from here - it will vanish soon.
+    have a physical representation (i.e. have an extent). 
+    Don't use messages from here - it will vanish soon.
 
     [Instance variables:]
 
-	width           <SmallInteger>  the width (device dependent, usually pixels or inches)
-	height          <SmallInteger>  the height (device dependent, usually pixels or inches)
+        width           <SmallInteger>  the width (device dependent, usually pixels or inches)
+        height          <SmallInteger>  the height (device dependent, usually pixels or inches)
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 "
 ! !
 
@@ -62,7 +64,16 @@
 "
     'Warning: DeviceGraphicsContext (' print. self name print. ') should not be created with new' printNL.
 "
-    ^ self onDevice:Screen current.
+    |device|
+
+    device := Screen current.
+    device isNil ifTrue:[
+        "/ there seems to be no current screen; open one.
+        Smalltalk openDisplay.
+        device := Screen current.
+    ].
+    
+    ^ self onDevice:device.
 !
 
 on:aDevice
--- a/HostGraphicsDevice.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/HostGraphicsDevice.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
 COPYRIGHT (c) 1997 by eXept Software AG / Claus Gittinger
 	      All Rights Reserved
@@ -138,7 +136,7 @@
     graphicsContexts := Registry new.
     deviceColors := Registry new.
     deviceCursors := Registry new.
-    deviceFonts := CachingRegistry new:20.
+    deviceFonts := CachingRegistry new:50.
 
     "Created: 24.2.1997 / 18:29:53 / cg"
 !
--- a/Image.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/Image.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
               All Rights Reserved
@@ -153,7 +151,7 @@
                                             monoDeviceForm and lowResDeviceForm are
 
         deviceForm          <Form>          the device form which gives the best
-                                            possible aproximation of the image on
+                                            possible approximation of the image on
                                             device using standard colors.
 
         monoDeviceForm      <Form>          the device form which gives a monochrome
@@ -1142,6 +1140,17 @@
     ^ self width:ext x height:ext y fromArray:bits
 !
 
+fromDeviceForm:aForm maskForm:aMaskFormOrNil
+    "create & return an image form aForm that is already on a device"
+
+    |img|
+
+    img := self newForDepth:aForm depth.
+    img fromDeviceForm:aForm maskForm:aMaskFormOrNil.
+
+    ^ img 
+!
+
 fromForm:aForm
     "create & return an Image given a aForm"
 
@@ -2851,6 +2860,14 @@
     ^ device
 !
 
+drawableId
+    "return the id of the image on the device.
+     Return nil, if the image is unassigned."
+
+    deviceForm isNil ifTrue:[^ nil].
+    ^ deviceForm drawableId
+!
+
 extent
     "return the images extent"
 
@@ -2894,11 +2911,7 @@
 !
 
 id
-    "return the id of the image on the device.
-     Return nil, if the image is unassigned."
-
-    deviceForm isNil ifTrue:[^ nil].
-    ^ deviceForm id
+    ^ self drawableId  
 !
 
 imageSequence
@@ -8824,7 +8837,7 @@
                  * colors in subCubeColors.
                  *
                  * since the error is at most 1/16 (i.e. roughly 6%),
-                 * dont care for searching the best - simply take the
+                 * don't care for searching the best - simply take the
                  * first color found there.
                  * (statistic reduces the error to even a smaller value).
                  * There is no real problem due to that error, since
@@ -12974,7 +12987,7 @@
         "/ for now, ignore all depth's which are neither 1 nor the
         "/ devices depth.
         "/ (actually, many devices can handle other pixMap formats,
-        "/ but I dont know (yet) how to pass the correct color info
+        "/ but I don't know (yet) how to pass the correct color info
 
         ((deviceImageDepth == 1) or:[deviceImageDepth == aDevice depth]) ifTrue:[
 
@@ -13091,6 +13104,19 @@
     "Modified: 10.1.1997 / 17:52:21 / cg"
 !
 
+fromDeviceForm:aForm maskForm:aMaskFormOrNil
+    device := aForm device.
+    self assert:device notNil.
+    photometric := aForm photometric.
+    deviceForm := aForm.
+    width := aForm width.
+    height := aForm height.
+
+    aMaskFormOrNil notNil ifTrue:[
+        mask := Image fromDeviceForm:aMaskFormOrNil maskForm:nil.
+    ].
+!
+
 greyByteMapForRange:range
     "return a collection to map from pixelValues to greyLevels
      in the range 0..range.
@@ -14615,33 +14641,26 @@
 
     device := aDrawable graphicsDevice.
 
-    (aDrawable isForm and:[aDrawable depth == 1]) ifTrue:[
-        "/ a monochrome bitmap ?
-        visType := #StaticGray.
-        ddepth := 1.
-    ] ifFalse:[
-        (aDrawable isForm) ifFalse:[
-            "
-             get some attributes of the display device
-            "
-            visType := device visualType.
-            ddepth := device depth.
-        ] ifTrue:[
+    aDrawable isForm ifTrue:[
+        aDrawable depth == 1 ifTrue:[
+            "/ a monochrome bitmap ?
+            visType := #StaticGray.
+            ddepth := 1.
+        ] ifFalse:[
             visType := aDrawable photometric.
             ddepth := aDrawable depth.
-        ].
-    ].
-
-    "/ kludge for 15bit XFree server
-    ddepth == 15 ifTrue:[
-        ddepth := 16
-    ].
-
-    aDrawable isForm ifTrue:[
+        ]. 
         photometric := aDrawable photometric.
         samplesPerPixel := ddepth == 24 ifTrue:3 ifFalse:1.
-        bitsPerSample := ddepth == 24 ifTrue:#[8 8 8 ] ifFalse:[ByteArray with:bpp].
+        bitsPerSample := ddepth == 24 ifTrue:#[8 8 8] ifFalse:[ByteArray with:bpp].
     ] ifFalse:[
+        "get some attributes of the display device"
+        visType := device visualType.
+        ddepth := device depth.
+        "/ kludge for 15bit XFree server
+        ddepth == 15 ifTrue:[
+            ddepth := 16
+        ].
         (visType == #StaticGray) ifTrue:[
             (device blackpixel == 0) ifTrue:[
                 photometric := #blackIs0
@@ -14700,8 +14719,6 @@
     ].
 
     bytesPerLine := (w * spaceBitsPerPixel + 31) // 32 * 4.
-    "/ inData := ByteArray uninitializedNew:(bytesPerLine * height).
-    inData := ByteArray new:(bytesPerLine * height).
 
     "
      get the pixels
@@ -14716,15 +14733,17 @@
                         yourself.
             inData := aDrawable bits.
         ] ifFalse:[
+            inData := ByteArray new:(bytesPerLine * height).
             info := device getBitsFromPixmapId:aDrawable id x:x y:y width:w height:h into:inData.
         ]
     ] ifFalse:[
+        inData := ByteArray new:(bytesPerLine * height).
         info := device getBitsFromViewId:aDrawable id x:x y:y width:w height:h into:inData.
     ].
 
     bitsPerPixelIn := info at:#bitsPerPixel.
 
-    isMSB := ((info at:#byteOrder) == #msbFirst).
+    isMSB := (info at:#byteOrder) == #msbFirst.
 
     "/
     "/ check if bitorder is what I like (msbFirst)
@@ -14755,7 +14774,7 @@
     maskB := info at:#blueMask ifAbsent:0.
 
     ((bytesPerLine ~~ bytesPerLineIn)
-    or:[bitsPerPixelIn ~~ bpp]) ifTrue:[
+     or:[bitsPerPixelIn ~~ bpp]) ifTrue:[
         tmpData := inData.
         inData := ByteArray uninitializedNew:(bytesPerLine * height).
 
@@ -15070,10 +15089,10 @@
     isLeft := leftOrRight sameAs:#left.
     isLeft ifTrue:[
         workPoint := (xRun - 1)@yRun.
-        [(
-            (tempForm pixelAtX:workPoint x y:workPoint y) == 0 and:[
-            (tempForm pixelAtX:workPoint x y:workPoint y + additionalY) == 1]) and:[
-            (tempForm pixelAtX:workPoint x - 1 y:workPoint y + additionalY) == 1]
+        [
+            ((tempForm pixelAtX:workPoint x y:workPoint y) == 0)
+            and:[ ((tempForm pixelAtX:workPoint x y:workPoint y + additionalY) == 1) 
+            and:[ ((tempForm pixelAtX:workPoint x - 1 y:workPoint y + additionalY) == 1) ]]
         ] whileTrue:[
             startX := workPoint x.
             endX isNil ifTrue:[endX := workPoint x].
@@ -15081,10 +15100,10 @@
         ].
     ] ifFalse:[
         workPoint := (xRun + 1)@yRun.
-        [(
-            (tempForm pixelAtX:workPoint x y:workPoint y) == 0 and:[
-            (tempForm pixelAtX:workPoint x y:workPoint y + additionalY) == 1]) and:[
-            (tempForm pixelAtX:workPoint x + 1 y:workPoint y + additionalY) == 1]
+        [
+            ((tempForm pixelAtX:workPoint x y:workPoint y) == 0)
+            and:[ ((tempForm pixelAtX:workPoint x y:workPoint y + additionalY) == 1) 
+            and:[ ((tempForm pixelAtX:workPoint x + 1 y:workPoint y + additionalY) == 1) ]]
         ] whileTrue:[
             endX := workPoint x.
             startX isNil ifTrue:[startX := workPoint x].
@@ -15141,10 +15160,10 @@
     isBottom := bottomOrTop sameAs:#bottom.
     isBottom ifTrue:[
         workPoint := xRun@(yRun + 1).
-        [(
-            (tempForm pixelAtX:workPoint x y:workPoint y) == 0 and:[
-            (tempForm pixelAtX:workPoint x + additionalX y:workPoint y) == 1]) and:[
-            (tempForm pixelAtX:workPoint x + additionalX y:workPoint y + 1) == 1]
+        [
+            ((tempForm pixelAtX:workPoint x y:workPoint y) == 0) 
+            and:[ ((tempForm pixelAtX:workPoint x + additionalX y:workPoint y) == 1) 
+            and:[ ((tempForm pixelAtX:workPoint x + additionalX y:workPoint y + 1) == 1) ]]
         ] whileTrue:[
             endY := workPoint y.
             startY isNil ifTrue:[startY := workPoint y].
@@ -15152,10 +15171,10 @@
         ].
     ] ifFalse:[
         workPoint := xRun@(yRun - 1).
-        [(
-            (tempForm pixelAtX:workPoint x y:workPoint y) == 0 and:[
-            (tempForm pixelAtX:workPoint x + additionalX y:workPoint y) == 1]) and:[
-            (tempForm pixelAtX:workPoint x + additionalX y:workPoint y - 1) == 1]
+        [
+            ((tempForm pixelAtX:workPoint x y:workPoint y) == 0) 
+            and:[ ((tempForm pixelAtX:workPoint x + additionalX y:workPoint y) == 1) 
+            and:[ ((tempForm pixelAtX:workPoint x + additionalX y:workPoint y - 1) == 1) ]]
         ] whileTrue:[
             startY := workPoint y.
             endY isNil ifTrue:[endY := workPoint y].
--- a/KeyboardForwarder.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/KeyboardForwarder.st	Fri Nov 18 21:26:33 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libview' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#KeyboardForwarder
 	instanceVariableNames:'sourceView destinationView destination condition filter'
 	classVariableNames:''
@@ -44,7 +46,7 @@
     Also, it allows to catch certain individual keys to ignore them or
     perform different functions.
 
-    Notice, that delegates dont have to be instances of
+    Notice, that delegates don't have to be instances of
     myself; any object with a protocol similar to mine can be used as
     a delegate. 
     (i.e. any object that responds to 
@@ -507,6 +509,6 @@
 !KeyboardForwarder class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libview/KeyboardForwarder.st,v 1.28 2014-03-21 18:30:26 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/ModalBox.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/ModalBox.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1990 by Claus Gittinger
 	      All Rights Reserved
@@ -609,7 +607,7 @@
 
 hideRequest
     "hide request from windowGroup (i.e. via Escape key).
-     Can be redefined in subclasses which dont like this"
+     Can be redefined in subclasses which don't like this"
 
     self hide
 !
--- a/ResourcePack.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/ResourcePack.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -55,31 +53,31 @@
     where 'className' is built by the usual abbreviation mechanism (see abbrev-files).
 
     Conditional mappings are possible, by including lines as:
-	#if <expression>
-	#endif
+        #if <expression>
+        #endif
     in the resourcefile. Example:
     file 'foo.rs':
-	#if Language == #de
-	'abort' 'Abbruch'
-	#endif
-	#if Language == #fr
-	'abort' 'canceller'
-	#endif
+        #if Language == #de
+        'abort' 'Abbruch'
+        #endif
+        #if Language == #fr
+        'abort' 'canceller'
+        #endif
 
     the corresponding resource-strings are accessed (from methods within the class)
     using:
-	resources string:'abort'
+        resources string:'abort'
 
     returning the mapped string (i.e. 'Abbruch' if the global Language is set
     to #de)..
 
     If no corresponding entry is found in the resources, the key is returned;
     alternatively, use:
-	resources string:'foo' default:'bar'
+        resources string:'foo' default:'bar'
     which returns 'bar', if no resource definition for 'foo' is found.
 
     Translations can also include arguments, such as:
-	resources string:'really delete %1' with:fileName
+        resources string:'really delete %1' with:fileName
 
     This scheme has the advantage, that you can write your programs using your
     native language strings. Later, when new languages are to be supported,
@@ -87,7 +85,7 @@
     all those strings. (find the keys by looking at users of resource or senders
     of 'string:*').
     Notice, that the grammar of different languages may imply a reordering,
-    so the above string becomes the german 'wollen Sie %1 wirklich löschen';
+    so the above string becomes the german 'wollen Sie %1 wirklich löschen';
     so using percent-placeholders is much better than simple concatenations of
     arguments to the question.
 
@@ -101,7 +99,7 @@
     Strings for unknown languages will come in english
     (which is better than nothing or empty button labels ;-)
 
-    Notice, that you can also translate engish to english, by providing an en.rs file.
+    Notice, that you can also translate english to english, by providing an en.rs file.
     This is sometimes useful to fix typing errors or bad syntax in the english,
     as sometimes made by the programmer, without a need to recompile or to also adjust other
     language translations.
@@ -110,43 +108,43 @@
     as typically used in the C-world.
     Simple use keys as argument, and provide translations for all languages (incl. english).
     For example:
-	Button label:(resources string:#BTN_FOO_LABEL)
+        Button label:(resources string:#BTN_FOO_LABEL)
 
 
     Summary:
-	in subclasses of View and ApplicationModel, instead of writing:
+        in subclasses of View and ApplicationModel, instead of writing:
 
-		...
-		b := Button label:'press me'
-		...
+                ...
+                b := Button label:'press me'
+                ...
 
-	always write:
+        always write:
 
-		...
-		b := Button label:(resources string:'press me')
-		...
+                ...
+                b := Button label:(resources string:'press me')
+                ...
 
-	if your class is not a subclass of one of the above, AND you need
-	resource translations, you won't inherit the resources variable
-	(which is automatically initialized).
-	In this case, you have to ask the ResourcePack class explicitely for
-	a corresponding package:
+        if your class is not a subclass of one of the above, AND you need
+        resource translations, you won't inherit the resources variable
+        (which is automatically initialized).
+        In this case, you have to ask the ResourcePack class explicitely for
+        a corresponding package:
 
-		ResourcePack for:aClassName
-	or (even better):
-		ResourcePack forPackage:aPackageID
+                ResourcePack for:aClassName
+        or (even better):
+                ResourcePack forPackage:aPackageID
 
-	as an example, see how the Date class gets the national names of
-	week & monthnames.
+        as an example, see how the Date class gets the national names of
+        week & monthnames.
 
     Debugging:
-	in the past, it happened that strings as returned by me were modified by someone else
-	(replaceAll:with:) and then lead to invalid presentation in the future.
-	To detect any bad guy which writes into one of my returned strings, set the DebugModifications
-	classVar to true. Then I will return ImmutableStrings which trap on writes.
+        in the past, it happened that strings as returned by me were modified by someone else
+        (replaceAll:with:) and then lead to invalid presentation in the future.
+        To detect any bad guy which writes into one of my returned strings, set the DebugModifications
+        classVar to true. Then I will return ImmutableStrings which trap on writes.
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 "
 !
 
--- a/SimpleView.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/SimpleView.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -156,7 +154,9 @@
 
 	shown                   <Boolean>               true if visible (false if iconified, unmapped or covered)
 
-	hiddenOnRealize         <Boolean>               dont show automatically when superview is realized
+	unused_hiddenOnRealize  <Boolean>               don't show automatically when superview is realized.
+							now encoded in the flags.
+							(kept to keep the instVar size constant)
 
 	name                    <String>                my name (future use for resources)
 
@@ -190,13 +190,14 @@
 
 	dependents              <nil | Collection>      who depends on me
 
-	layoutManager
-
-	visibilityChannel
-
-	helpKey
-
-	dropTarget
+	layoutManager                                   currently unused; will be responsible for
+							child layout management
+
+	visibilityChannel                               valueHolder to control the visiblity
+
+	helpKey                                         for tooltips
+
+	dropTarget                                      for drag&drop
 
     (*) about to be changed to use preferredExtent as a cache and explicitExtent as
 	an overwrite value.
@@ -688,7 +689,7 @@
 
     For textViews, the above is also valid, except if the menuHolder is explicitely
     set - in this case, that one provides the menu; not the model.
-    Dont get confused by the fact that menuHolders are only supported
+    Don't get confused by the fact that menuHolders are only supported
     by textViews.
 
     example: (in your application, the plug would be your application, topView or model)
@@ -780,12 +781,12 @@
 
 initialize
     DefaultStyle isNil ifTrue:[
-        Font initialize.
-        Form initialize.
-        Color initialize.
+	Font initialize.
+	Form initialize.
+	Color initialize.
     ].
     self == SimpleView ifTrue:[
-        Smalltalk addDependent:self   "/ to get language changes
+	Smalltalk addDependent:self   "/ to get language changes
     ].
 
     ReturnFocusWhenClosingModalBoxes := true. "/ false.
@@ -848,14 +849,14 @@
 
     newView := self basicNew.
     aView notNil ifTrue:[
-        viewsDevice := aView graphicsDevice.
+	viewsDevice := aView graphicsDevice.
 "/      newView container:aView.
     ] ifFalse:[
-        viewsDevice := Screen current
+	viewsDevice := Screen current
     ].
     newView initializeForDevice:viewsDevice.
     (viewsDevice supportsNativeWidgetType:newView nativeWindowType) ifTrue:[
-        newView beNativeWidget
+	newView beNativeWidget
     ].
     aView notNil ifTrue:[aView addSubView:newView].
     ^ newView
@@ -904,9 +905,9 @@
     |viewsDevice|
 
     anotherView notNil ifTrue:[
-        viewsDevice := anotherView graphicsDevice.
+	viewsDevice := anotherView graphicsDevice.
     ] ifFalse:[
-        viewsDevice := Screen current.
+	viewsDevice := Screen current.
     ].
     ^ self onDevice:viewsDevice
 
@@ -1107,12 +1108,12 @@
 
     DefaultFont := aFont.
     aFont notNil ifTrue:[
-        Display notNil ifTrue:[
-            f := aFont onDevice:(Screen current).
-            f notNil ifTrue:[
-                DefaultFont := f.
-            ]
-        ]
+	Display notNil ifTrue:[
+	    f := aFont onDevice:(Screen current).
+	    f notNil ifTrue:[
+		DefaultFont := f.
+	    ]
+	]
     ]
 
     "Modified: 18.3.1996 / 12:56:20 / cg"
@@ -1134,7 +1135,7 @@
     DefaultStyle := aStyle.
 
     MIMETypeIconLibrary notNil ifTrue:[
-        MIMETypeIconLibrary flushIcons
+	MIMETypeIconLibrary flushIcons
     ].
 
     "/ no need to read the stylesheet always here
@@ -1146,9 +1147,9 @@
     "/ no need to read the stylesheet, then.
     "/ used to be unconditional, before.
     StyleSheet notNil ifTrue:[
-        (Screen notNil and:[Screen current notNil]) ifTrue:[
-            self readStyleSheetAndUpdateAllStyleCaches.
-        ].
+	(Screen notNil and:[Screen current notNil]) ifTrue:[
+	    self readStyleSheetAndUpdateAllStyleCaches.
+	].
     ].
 
     "
@@ -1180,20 +1181,20 @@
     |iconLibraryClass |
 
     DefaultStyle isNil ifTrue:[
-        self setDefaultStyle
+	self setDefaultStyle
     ].
 
     StyleSheet := ViewStyle fromFile:(DefaultStyle , '.style').
     StyleSheet fileReadFailed ifTrue:[
-        ('SimpleView [warning]: ***** no styleSheet for ' , DefaultStyle , '-style.') errorPrintCR.
-        DefaultStyle ~~ #normal ifTrue:[
-            DefaultStyle := #normal.
-            StyleSheet := ViewStyle fromFile:(DefaultStyle , '.style').
-
-            StyleSheet fileReadFailed ifTrue:[
-                'SimpleView [warning]: not even a styleSheet for normal-style (using ugly defaults).' errorPrintCR.
-            ]
-        ]
+	('SimpleView [warning]: ***** no styleSheet for ' , DefaultStyle , '-style.') errorPrintCR.
+	DefaultStyle ~~ #normal ifTrue:[
+	    DefaultStyle := #normal.
+	    StyleSheet := ViewStyle fromFile:(DefaultStyle , '.style').
+
+	    StyleSheet fileReadFailed ifTrue:[
+		'SimpleView [warning]: not even a styleSheet for normal-style (using ugly defaults).' errorPrintCR.
+	    ]
+	]
     ].
 
     iconLibraryClass := StyleSheet at:#ToolbarIconLibrary.
@@ -1249,28 +1250,28 @@
     |defStyle|
 
     true "DefaultStyle isNil" ifTrue:[
-        defStyle := OperatingSystem getEnvironment:'STX_VIEWSTYLE'.
-        defStyle notNil ifTrue:[
-            DefaultStyle := defStyle asSymbol.
-        ] ifFalse:[
-            "/ use XP for both linux and older windows systems;
-            DefaultStyle := ViewStyle msWindowsXP.
-
-            OperatingSystem isMSWINDOWSlike ifTrue:[
-                "/ use Vista for vista and newer systems;
-                OperatingSystem isVistaLike ifTrue:[
-                    DefaultStyle := ViewStyle msWindowsVista.
-                    OperatingSystem isWin8Like ifTrue:[
-                        "/ use win8 for 8 and newer systems;
-                        DefaultStyle := ViewStyle msWindows8
-                    ].
-                ].
-            ] ifFalse:[
-                OperatingSystem isOSXlike ifTrue:[
-                    DefaultStyle := #macosx
-                ].
-            ].
-        ].
+	defStyle := OperatingSystem getEnvironment:'STX_VIEWSTYLE'.
+	defStyle notNil ifTrue:[
+	    DefaultStyle := defStyle asSymbol.
+	] ifFalse:[
+	    "/ use XP for both linux and older windows systems;
+	    DefaultStyle := ViewStyle msWindowsXP.
+
+	    OperatingSystem isMSWINDOWSlike ifTrue:[
+		"/ use Vista for vista and newer systems;
+		OperatingSystem isVistaLike ifTrue:[
+		    DefaultStyle := ViewStyle msWindowsVista.
+		    OperatingSystem isWin8Like ifTrue:[
+			"/ use win8 for 8 and newer systems;
+			DefaultStyle := ViewStyle msWindows8
+		    ].
+		].
+	    ] ifFalse:[
+		OperatingSystem isOSXlike ifTrue:[
+		    DefaultStyle := #macosx
+		].
+	    ].
+	].
     ].
 
     "Modified: / 03-02-2011 / 21:41:35 / cg"
@@ -1320,14 +1321,14 @@
     SimpleView updateStyleCache.
     SimpleView allSubclassesDo:[:aClass |
         aClass defaultFont:nil.
-        (aClass class includesSelector:#updateStyleCache) ifTrue:[
-            aClass updateStyleCache
-        ].
+	(aClass class includesSelector:#updateStyleCache) ifTrue:[
+	    aClass updateStyleCache
+	].
     ].
 
     "/ use #at: to avoid introducing a depency to libview2
     (Smalltalk at:#MIMETypeIconLibrary) notNil ifTrue:[
-        (Smalltalk at:#MIMETypeIconLibrary) flushIcons
+	(Smalltalk at:#MIMETypeIconLibrary) flushIcons
     ].
 
 
@@ -1953,15 +1954,15 @@
     |clr|
 
     (superView notNil and:[superView isBorderedWrapper]) ifTrue:[
-        ^ superView borderColor
+	^ superView borderColor
     ].
 
     "/ ^ borderColor
     border notNil ifTrue:[
-        clr := border color
+	clr := border color
     ].
     clr isNil ifTrue:[
-        ^ self blackColor
+	^ self blackColor
     ].
     ^ clr.
 
@@ -2002,18 +2003,18 @@
     "set the borderShape to aForm"
 
     aForm isNil ifTrue:[
-        viewShape := nil.
-        self drawableId notNil ifTrue:[
-            device setWindowBorderShape:nil in:self drawableId
-        ]
+	viewShape := nil.
+	self drawableId notNil ifTrue:[
+	    device setWindowBorderShape:nil in:self drawableId
+	]
     ] ifFalse:[
-        viewShape isNil ifTrue:[
-            viewShape := ArbitraryViewShape new
-        ].
-        viewShape borderShapeForm:aForm.
-        self drawableId notNil ifTrue:[
-            device setWindowBorderShape:(aForm id) in:self drawableId
-        ]
+	viewShape isNil ifTrue:[
+	    viewShape := ArbitraryViewShape new
+	].
+	viewShape borderShapeForm:aForm.
+	self drawableId notNil ifTrue:[
+	    device setWindowBorderShape:(aForm id) in:self drawableId
+	]
     ]
 
     "Modified: 18.9.1997 / 11:09:40 / cg"
@@ -2166,10 +2167,10 @@
     "return the color to be used for lighted edges (3D only)"
 
     lightColor isNil ifTrue:[
-        |avgColor|
+	|avgColor|
         
-        avgColor := viewBackground averageColorIn:(0@0 corner:7@7).
-        lightColor := avgColor lightened.
+	avgColor := viewBackground averageColorIn:(0@0 corner:7@7).
+	lightColor := avgColor lightened.
     ].
     ^ lightColor
 !
@@ -2220,10 +2221,10 @@
     "return the color to be used for shadowed edges (3D only)"
 
     shadowColor isNil ifTrue:[
-        |avgColor|
-
-        avgColor := viewBackground averageColorIn:(0@0 corner:7@7).
-        shadowColor := avgColor darkened.
+	|avgColor|
+
+	avgColor := viewBackground averageColorIn:(0@0 corner:7@7).
+	shadowColor := avgColor darkened.
     ].
     ^ shadowColor
 !
@@ -2246,7 +2247,7 @@
     self assert:(something notNil) message:'invalid viewBackground argument'.
 
     something isColor ifTrue:[
-        device hasGrayscales ifTrue:[
+        (device notNil and:[device hasGrayscales]) ifTrue:[
             avgColor := something averageColorIn:(0@0 corner:7@7).
             shadowColor := avgColor darkened "on:device".
             lightColor := avgColor lightened "on:device".
@@ -2273,19 +2274,19 @@
     "set the viewShape to aForm"
 
     aForm isNil ifTrue:[
-        viewShape := nil.
-        self drawableId notNil ifTrue:[
-            device setWindowShape:nil in:self drawableId
-        ]
+	viewShape := nil.
+	self drawableId notNil ifTrue:[
+	    device setWindowShape:nil in:self drawableId
+	]
     ] ifFalse:[
-        viewShape isNil ifTrue:[
-            viewShape := ArbitraryViewShape new
-        ].
-
-        viewShape viewShapeForm:aForm.
-        self drawableId notNil ifTrue:[
-            device setWindowShape:(aForm id) in:self drawableId
-        ]
+	viewShape isNil ifTrue:[
+	    viewShape := ArbitraryViewShape new
+	].
+
+	viewShape viewShapeForm:aForm.
+	self drawableId notNil ifTrue:[
+	    device setWindowShape:(aForm id) in:self drawableId
+	]
     ]
 
     "Modified: 18.9.1997 / 11:11:04 / cg"
@@ -2732,7 +2733,7 @@
 	    self extentChangedFlag:true
 	]
     ] ifFalse:[
-        extentRule := nil.
+	extentRule := nil.
 	w := extent x.
 	h := extent y.
 	w isNil ifTrue:[w := width].
@@ -2843,7 +2844,7 @@
 !
 
 initialExtent:extent
-    "set the views extent, but dont change its explicitExtent setting.
+    "set the views extent, but don't change its explicitExtent setting.
      a variant of #extent."
 
     |expl|
@@ -2854,13 +2855,13 @@
 !
 
 initialHeight:aNumber
-    "set the views height in pixels, but dont change its explicitExtent setting"
+    "set the views height in pixels, but don't change its explicitExtent setting"
 
     self initialExtent:(width @ aNumber)
 !
 
 initialWidth:aNumber
-    "set the views width in pixels, but dont change its explicitExtent setting"
+    "set the views width in pixels, but don't change its explicitExtent setting"
 
     self initialExtent:(aNumber @ height)
 !
@@ -3021,19 +3022,19 @@
     cornerVisible := myDevice pointIsVisible:corner.
 
     (myDevice pointsAreOnSameMonitor:origin and:corner) ifTrue:[
-        referencePoint := origin.
+	referencePoint := origin.
     ] ifFalse:[
-        originVisible ifTrue:[
-            "origin is visible"
-            referencePoint := origin.
-        ] ifFalse:[
-            cornerVisible notNil ifTrue:[
-                "corner is visible"
-                referencePoint := corner.
-            ] ifFalse:[
-                referencePoint := 1@1.
-            ].
-        ].
+	originVisible ifTrue:[
+	    "origin is visible"
+	    referencePoint := origin.
+	] ifFalse:[
+	    cornerVisible notNil ifTrue:[
+		"corner is visible"
+		referencePoint := corner.
+	    ] ifFalse:[
+		referencePoint := 1@1.
+	    ].
+	].
     ].
     deviceBounds := myDevice monitorBoundsAt:referencePoint.
 
@@ -3046,40 +3047,40 @@
     cornerVisible ifTrue:[ deviceBottom := deviceBottom min:(myDevice usableHeightAt:corner) ].
 
     corner y > deviceBottom ifTrue:[
-        cornerVisible := false.
+	cornerVisible := false.
     ].
 
     UserPreferences current forceWindowsIntoMonitorBounds ifFalse:[
-        (originVisible and:[cornerVisible]) ifTrue:[^ self].
+	(originVisible and:[cornerVisible]) ifTrue:[^ self].
     ].
 
     "/ deviceRight := deviceRight min:device usableWidth.
     originVisible ifFalse:[
-        cornerVisible ifFalse:[
-            newTop := deviceBottom - height.
-            newLeft := deviceRight - width.
-            newLeft := newLeft max:deviceLeft.
-            newTop := newTop max:deviceTop.
-        ] ifTrue:[
-            "/ origin is not; corner is in
-            newLeft := (deviceLeft max:newLeft).
-            newTop := (deviceTop max:newTop).
-        ].
+	cornerVisible ifFalse:[
+	    newTop := deviceBottom - height.
+	    newLeft := deviceRight - width.
+	    newLeft := newLeft max:deviceLeft.
+	    newTop := newTop max:deviceTop.
+	] ifTrue:[
+	    "/ origin is not; corner is in
+	    newLeft := (deviceLeft max:newLeft).
+	    newTop := (deviceTop max:newTop).
+	].
     ] ifTrue:[
-        "/ notice, the position-dependent query: if there is a higher secondary screen,
-        "/ this makes a difference in where a popUpMenu is allowed...
-        (corner y > deviceBottom) ifTrue:[
-            newTop := deviceBottom - height
-        ].
-        (corner x > deviceRight) ifTrue:[
-            newLeft := deviceRight - width
-        ].
-        newLeft := newLeft max:deviceLeft.
-        newTop := newTop max:deviceTop.
+	"/ notice, the position-dependent query: if there is a higher secondary screen,
+	"/ this makes a difference in where a popUpMenu is allowed...
+	(corner y > deviceBottom) ifTrue:[
+	    newTop := deviceBottom - height
+	].
+	(corner x > deviceRight) ifTrue:[
+	    newLeft := deviceRight - width
+	].
+	newLeft := newLeft max:deviceLeft.
+	newTop := newTop max:deviceTop.
     ].
 
     ((newTop ~~ top) or:[newLeft ~~ left]) ifTrue:[
-        self origin:newLeft @ newTop
+	self origin:newLeft @ newTop
     ].
 
     "Modified: / 27-10-2012 / 13:15:58 / cg"
@@ -3104,35 +3105,35 @@
 "/    ].
 
     device supportsArbitraryShapedViews ifTrue:[
-        extent := self extent.
-        w := extent x.
-        h := extent y.
-        borderForm := Form extent:extent.
-        shapeForm  := Form extent:extent.
-
-        borderForm fillArcX:0 y:0
-                  width:w
-                 height:h
-                   from:0
-                  angle:360.
-
-        opaque ifFalse:[
-            f := borderForm.
-            borderForm foreground:(Color colorId:0).
-        ] ifTrue:[
-            f := shapeForm.
-            shapeForm foreground:(Color colorId:1).
-        ].
-
-        f fillArcX:(lw := gc lineWidth) y:lw
-                width:w - (bw * 2)
-               height:h - (bw * 2)
-                 from:0
-                angle:360.
-
-        self borderShape:borderForm.
-        self viewShape:shapeForm.
-        ^ self.
+	extent := self extent.
+	w := extent x.
+	h := extent y.
+	borderForm := Form extent:extent.
+	shapeForm  := Form extent:extent.
+
+	borderForm fillArcX:0 y:0
+		  width:w
+		 height:h
+		   from:0
+		  angle:360.
+
+	opaque ifFalse:[
+	    f := borderForm.
+	    borderForm foreground:(Color colorId:0).
+	] ifTrue:[
+	    f := shapeForm.
+	    shapeForm foreground:(Color colorId:1).
+	].
+
+	f fillArcX:(lw := gc lineWidth) y:lw
+		width:w - (bw * 2)
+	       height:h - (bw * 2)
+		 from:0
+		angle:360.
+
+	self borderShape:borderForm.
+	self viewShape:shapeForm.
+	^ self.
 
 "/
 "/        extent := self extent.
@@ -3183,28 +3184,28 @@
 "/    ].
 
     device supportsArbitraryShapedViews ifTrue:[
-        extent := self extent.
-        w := extent x.
-        h := extent y.
-        borderForm := Form extent:extent.
-        shapeForm  := Form extent:extent.
-
-        borderForm
-            fillRectangleX:0 y:0
-            width:w
-            height:h.
-
-        f := borderForm.
-        borderForm foreground:(Color colorId:0).
-
-        borderForm
-            fillRectangleX:bw y:bw
-            width:w - (bw * 2)
-            height:h - (bw * 2).
-
-        self borderShape:borderForm.
-        self viewShape:shapeForm.
-        ^ self.
+	extent := self extent.
+	w := extent x.
+	h := extent y.
+	borderForm := Form extent:extent.
+	shapeForm  := Form extent:extent.
+
+	borderForm
+	    fillRectangleX:0 y:0
+	    width:w
+	    height:h.
+
+	f := borderForm.
+	borderForm foreground:(Color colorId:0).
+
+	borderForm
+	    fillRectangleX:bw y:bw
+	    width:w - (bw * 2)
+	    height:h - (bw * 2).
+
+	self borderShape:borderForm.
+	self viewShape:shapeForm.
+	^ self.
     ]
 !
 
@@ -3352,17 +3353,17 @@
     sumX := 0.
     sumY := 0.
     [currentView notNil] whileTrue:[
-        (currentView == aView) ifTrue:[
-            ^ (sumX @ sumY)
-        ].
-        bw := currentView borderWidth.
-        sumX := sumX + (currentView left) + bw.
-        sumY := sumY + (currentView top) + bw.
-        currentView := currentView superView
+	(currentView == aView) ifTrue:[
+	    ^ (sumX @ sumY)
+	].
+	bw := currentView borderWidth.
+	sumX := sumX + (currentView left) + bw.
+	sumY := sumY + (currentView top) + bw.
+	currentView := currentView superView
     ].
     (aView isNil or:[aView == device rootView]) ifTrue:[
-        "return relative to screen ..."
-        ^ (sumX @ sumY)
+	"return relative to screen ..."
+	^ (sumX @ sumY)
     ].
     ^ nil
 
@@ -3402,8 +3403,8 @@
 
     "MB:added  {" "needed if layout is used e.g. POUEditor"
     layout notNil ifTrue:[
-        layout isRectangle ifTrue:[
-            ^ 0@0
+	layout isRectangle ifTrue:[
+	    ^ 0@0
         ].    
 	^(layout rightFraction) @ (layout bottomFraction)
     ].
@@ -3445,8 +3446,8 @@
 
     "MB:added  {"  "needed if layout is used e.g. POUEditor"
     layout notNil ifTrue:[
-        layout isRectangle ifTrue:[
-            ^ 0@0
+	layout isRectangle ifTrue:[
+	    ^ 0@0
         ].    
 	^(layout leftFraction) @ (layout topFraction)
     ].
@@ -3972,14 +3973,14 @@
      the model first, then use the views menu.
     "
     (menuHolder respondsTo:sym) ifFalse:[
-        (self respondsTo:sym) ifTrue:[
-            menuHolder := self
-        ]
+	(self respondsTo:sym) ifTrue:[
+	    menuHolder := self
+	]
     ].
 
     sym numArgs > 0 ifTrue:[
-        "/ squeak compatibility (with args): create the empty menu here, let model add items
-        ^ menuHolder perform:sym withOptionalArgument:(Menu new) and:(device shiftDown).
+	"/ squeak compatibility (with args): create the empty menu here, let model add items
+	^ menuHolder perform:sym withOptionalArgument:(Menu new) and:(device shiftDown).
     ].
 
     "
@@ -4002,7 +4003,7 @@
      when the view is resized."
 
     bitGravity ~~ gravity ifTrue:[
-        bitGravity := gravity.
+	bitGravity := gravity.
 	gc bitGravity:gravity.
     ]
 !
@@ -4016,53 +4017,53 @@
 
     currentClippingBounds := gc clippingBoundsOrNil.
     (currentClippingBounds = aRectangleOrNil) ifTrue:[
-        ^ self
+	^ self
     ].
     newBounds := aRectangleOrNil.
 
     aRectangleOrNil notNil ifTrue:[
-        |currentTransformation|
-
-        x := aRectangleOrNil left.
-        y := aRectangleOrNil top.
-        w := aRectangleOrNil width.
-        h := aRectangleOrNil height.
-        currentTransformation := gc transformation.
-        currentTransformation notNil ifTrue:[
-            x := currentTransformation applyToX:x.
-            y := currentTransformation applyToY:y.
-            w := currentTransformation applyScaleX:w.
-            h := currentTransformation applyScaleY:h.
-        ].
-        (x class ~~ SmallInteger) ifTrue:[
-            w := w + (x - x truncated).
-            x := x truncated
-        ].
-        (y class ~~ SmallInteger) ifTrue:[
-            h := h + (y - y truncated).
-            y := y truncated
-        ].
-        (w class ~~ SmallInteger) ifTrue:[
-            w := w truncated + 1
-        ].
-        (h class ~~ SmallInteger) ifTrue:[
-            h := h truncated + 1
-        ].
-        x < margin ifTrue:[
-            x := margin.
-        ].
-        y < margin ifTrue:[
-            y := margin.
-        ].
-        x + w - 1 >= (width-margin) ifTrue:[
-            w := width - margin - x
-        ].
-        y + h - 1 >= (height-margin) ifTrue:[
-            h := height - margin - y
-        ].
-        w := w max:0.
-        h := h max:0.
-        newBounds := Rectangle left:x top:y width:w height:h.
+	|currentTransformation|
+
+	x := aRectangleOrNil left.
+	y := aRectangleOrNil top.
+	w := aRectangleOrNil width.
+	h := aRectangleOrNil height.
+	currentTransformation := gc transformation.
+	currentTransformation notNil ifTrue:[
+	    x := currentTransformation applyToX:x.
+	    y := currentTransformation applyToY:y.
+	    w := currentTransformation applyScaleX:w.
+	    h := currentTransformation applyScaleY:h.
+	].
+	(x class ~~ SmallInteger) ifTrue:[
+	    w := w + (x - x truncated).
+	    x := x truncated
+	].
+	(y class ~~ SmallInteger) ifTrue:[
+	    h := h + (y - y truncated).
+	    y := y truncated
+	].
+	(w class ~~ SmallInteger) ifTrue:[
+	    w := w truncated + 1
+	].
+	(h class ~~ SmallInteger) ifTrue:[
+	    h := h truncated + 1
+	].
+	x < margin ifTrue:[
+	    x := margin.
+	].
+	y < margin ifTrue:[
+	    y := margin.
+	].
+	x + w - 1 >= (width-margin) ifTrue:[
+	    w := width - margin - x
+	].
+	y + h - 1 >= (height-margin) ifTrue:[
+	    h := height - margin - y
+	].
+	w := w max:0.
+	h := h max:0.
+	newBounds := Rectangle left:x top:y width:w height:h.
     ].
     gc deviceClippingBounds:newBounds
 
@@ -4140,7 +4141,7 @@
      when the superView is resized."
 
     viewGravity ~~ gravity ifTrue:[
-        viewGravity := gravity.
+	viewGravity := gravity.
 	gc viewGravity:gravity.
     ]
 ! !
@@ -4479,9 +4480,9 @@
      be mapped (i.e. shown) automatically when the superview is realized.
      The hiddenOnRealize flag is useful to create views which are
      to be made visible conditionally or later.
+     Notice: if there is a visibilityChanne, this static flag is ignored.
      For ST-80 compatibility, please use #beVisible / #beInvisible."
 
-    "/ hiddenOnRealize := aBoolean
     aBoolean ifTrue:[
 	flagBits := flagBits bitOr:FlagHiddenOnRealize
     ] ifFalse:[
@@ -4505,9 +4506,9 @@
      (especially in panels), which otherwise occur while subviews are removed."
 
     aBoolean ifTrue:[
-        flagBits := flagBits bitOr:FlagBeingDestroyed
+	flagBits := flagBits bitOr:FlagBeingDestroyed
     ] ifFalse:[
-        flagBits := flagBits bitClear:FlagBeingDestroyed
+	flagBits := flagBits bitClear:FlagBeingDestroyed
     ].
 !
 
@@ -4515,10 +4516,14 @@
     "return true, if the receiver will NOT be mapped when realized.
      False otherwise.
      The hiddenOnRealize flag is useful to create views which are
-     to be made visible conditionally or later."
-
-    ^ flagBits bitTest:FlagHiddenOnRealize.
-
+     to be made visible conditionally or later.
+     Notice: if there is a visibilityChanne, the static flag is ignored."
+
+    visibilityChannel isNil ifTrue:[
+        ^ flagBits bitTest:FlagHiddenOnRealize.
+    ].
+    ^ visibilityChannel value not
+    
     "Created: 17.6.1997 / 11:21:42 / cg"
 !
 
@@ -4678,7 +4683,7 @@
 
 addComponent:aComponent
     "components (i.e. gadgets or lightweight views) are being prepared.
-     Dont use this right now for non-views"
+     Don't use this right now for non-views"
 
     aComponent isView ifTrue:[
 	self addSubView:aComponent
@@ -4790,7 +4795,7 @@
 
 component:aComponent
     "components (i.e. gadgets or lightweight views) are being prepared.
-     Dont use this right now for non-views"
+     Don't use this right now for non-views"
 
     aComponent origin:0.0@0.0 corner:1.0@1.0.
     aComponent isView ifTrue:[
@@ -4832,7 +4837,7 @@
 
 removeComponent:aComponent
     "components (i.e. gadgets or lightweight views) are being prepared.
-     Dont use this right now for non-views"
+     Don't use this right now for non-views"
 
     aComponent isView ifTrue:[
 	self removeSubView:aComponent
@@ -4863,10 +4868,10 @@
 
     aView container:self.
     (aView graphicsDevice ~~ device) ifTrue:[
-        'SimpleView [warning]: subview (' errorPrint. aView class name errorPrint.
-        ') has different device than me (' errorPrint.
-        self class name errorPrint. ').' errorPrintCR.
-        aView device:device
+	'SimpleView [warning]: subview (' errorPrint. aView class name errorPrint.
+	') has different device than me (' errorPrint.
+	self class name errorPrint. ').' errorPrintCR.
+	aView device:device
     ].
 
     "Created: 9.5.1996 / 00:46:59 / cg"
@@ -4892,9 +4897,9 @@
     "an update request"
 
     aspect == #sizeOfView ifTrue:[
-        "one of the views we depend on changed its size"
-        "/ cg: #containerChangedSize has already been sent by the caller
-        ^ self "containerChangedSize".
+	"one of the views we depend on changed its size"
+	"/ cg: #containerChangedSize has already been sent by the caller
+	^ self "containerChangedSize".
     ].
     super update:aspect with:aParameter from:changedObject
 
@@ -4943,7 +4948,7 @@
 	cursors := bitmaps collect:[:form | (Cursor sourceForm:form
 						      maskForm:maskForm
 							  hotX:8
-                                                          hotY:8) onDevice:device].
+							  hotY:8) onDevice:device].
 
 	process := [
 		    Delay waitForSeconds:0.25.
@@ -5019,7 +5024,7 @@
 
     dependents isNil ifTrue:[^ #()].
     dependents isCollection ifTrue:[
-        ^ dependents
+	^ dependents
     ].
     ^ IdentitySet with:dependents
 
@@ -5034,11 +5039,11 @@
     |dep|
 
     aCollection size == 1 ifTrue:[
-        dep := aCollection first.
-        dep isCollection ifFalse:[
-            dependents := aCollection first.
-            ^ self
-        ]
+	dep := aCollection first.
+	dep isCollection ifFalse:[
+	    dependents := aCollection first.
+	    ^ self
+	]
     ].
     dependents := aCollection
 
@@ -5054,11 +5059,11 @@
 
     deps := dependents.
     deps notNil ifTrue:[
-        deps isCollection ifTrue:[
-            deps do:aBlock
-        ] ifFalse:[
-            aBlock value:deps
-        ]
+	deps isCollection ifTrue:[
+	    deps do:aBlock
+	] ifFalse:[
+	    aBlock value:deps
+	]
     ]
 
     "Created: 11.6.1997 / 13:10:51 / cg"
@@ -5341,33 +5346,33 @@
     count == 0 ifTrue:[^ self].
 
     (count < 0) ifTrue:[
-        leftFg := shadowColor.
-        leftHalfFg := halfShadowColor.
-        count := count negated.
+	leftFg := shadowColor.
+	leftHalfFg := halfShadowColor.
+	count := count negated.
     ] ifFalse:[
-        leftFg := lightColor.
-        leftHalfFg := halfLightColor.
+	leftFg := lightColor.
+	leftHalfFg := halfLightColor.
     ].
     leftHalfFg isNil ifTrue:[
-        leftHalfFg := leftFg
+	leftHalfFg := leftFg
     ].
 
     ((edgeStyle == #soft) and:[level > 0]) ifTrue:[
-        paint := leftHalfFg
+	paint := leftHalfFg
     ] ifFalse:[
-        paint := leftFg
+	paint := leftFg
     ].
     super paint:paint.
     super lineWidth:0.
 
     b := height - 1.
     0 to:(count - 1) do:[:i |
-        super displayDeviceLineFromX:i y:i toX:i y:(b - i)
+	super displayDeviceLineFromX:i y:i toX:i y:(b - i)
     ].
 
     ((edgeStyle == #soft) and:[level > 2]) ifTrue:[
-        super paint:(device blackColor).
-        super displayDeviceLineFromX:0 y:0 toX:0 y:b.
+	super paint:(device blackColor).
+	super displayDeviceLineFromX:0 y:0 toX:0 y:b.
     ].
 
     self edgeDrawn:#left.
@@ -5442,32 +5447,32 @@
     count == 0 ifTrue:[^ self].
 
     (count < 0) ifTrue:[
-        topFg := shadowColor.
-        topHalfFg := halfShadowColor.
-        count := count negated
+	topFg := shadowColor.
+	topHalfFg := halfShadowColor.
+	count := count negated
     ] ifFalse:[
-        topFg := lightColor.
-        topHalfFg := halfLightColor.
+	topFg := lightColor.
+	topHalfFg := halfLightColor.
     ].
     topHalfFg isNil ifTrue:[
-        topHalfFg := topFg
+	topHalfFg := topFg
     ].
 
     ((edgeStyle == #soft) and:[level > 0]) ifTrue:[
-        paint := topHalfFg
+	paint := topHalfFg
     ] ifFalse:[
-        paint := topFg
+	paint := topFg
     ].
     super paint:paint.
     super lineWidth:0.
 
     r := width - 1.
     0 to:(count - 1) do:[:i |
-        super displayDeviceLineFromX:i y:y+i toX:(r - i) y:y+i
+	super displayDeviceLineFromX:i y:y+i toX:(r - i) y:y+i
     ].
     ((edgeStyle == #soft) and:[level > 2]) ifTrue:[
-        super paint:(device blackColor).
-        super displayDeviceLineFromX:0 y:y+0 toX:r y:y+0.
+	super paint:(device blackColor).
+	super displayDeviceLineFromX:0 y:y+0 toX:r y:y+0.
     ].
 
     self edgeDrawn:#top.
@@ -5487,32 +5492,32 @@
     count == 0 ifTrue:[^ self].
 
     (count < 0) ifTrue:[
-        topFg := shadowColor.
-        topHalfFg := halfShadowColor.
-        count := count negated
+	topFg := shadowColor.
+	topHalfFg := halfShadowColor.
+	count := count negated
     ] ifFalse:[
-        topFg := lightColor.
-        topHalfFg := halfLightColor.
+	topFg := lightColor.
+	topHalfFg := halfLightColor.
     ].
     topHalfFg isNil ifTrue:[
-        topHalfFg := topFg
+	topHalfFg := topFg
     ].
 
     ((edgeStyle == #soft) and:[level > 0]) ifTrue:[
-        paint := topHalfFg
+	paint := topHalfFg
     ] ifFalse:[
-        paint := topFg
+	paint := topFg
     ].
     super paint:paint.
     super lineWidth:0.
 
     r := width - 1.
     0 to:(count - 1) do:[:i |
-        super displayDeviceLineFromX:i y:i toX:(r - i) y:i
+	super displayDeviceLineFromX:i y:i toX:(r - i) y:i
     ].
     ((edgeStyle == #soft) and:[level > 2]) ifTrue:[
-        super paint:(device blackColor).
-        super displayDeviceLineFromX:0 y:0 toX:r y:0.
+	super paint:(device blackColor).
+	super displayDeviceLineFromX:0 y:0 toX:r y:0.
     ].
 
     self edgeDrawn:#top.
@@ -5860,74 +5865,74 @@
 
     (superView isNil
     and:[self drawableId notNil]) ifTrue:[
-        "/ have to be careful - some window managers (motif) wrap another
-        "/ view around and the reported origin is relative to that.
-        "/ not relative to the screen.
-        p := device translatePoint:0@0 fromView:self toView:nil.
-        p := p + self borderWidth.
-        left := p x.
-        top := p y.
+	"/ have to be careful - some window managers (motif) wrap another
+	"/ view around and the reported origin is relative to that.
+	"/ not relative to the screen.
+	p := device translatePoint:0@0 fromView:self toView:nil.
+	p := p + self borderWidth.
+	left := p x.
+	top := p y.
     ].
 
     ((width ~~ newWidth) or:[height ~~ newHeight]) ifTrue:[
-        realized ifFalse:[
-            width := newWidth.
-            height := newHeight.
-            self extentChangedFlag:true.
-            ^ self
-        ].
-
-        ((newWidth <= width) and:[newHeight <= height]) ifTrue:[
-            how := #smaller
-        ] ifFalse:[
-            ((newWidth >= width) and:[newHeight >= height]) ifTrue:[
-                how := #larger
-            ]
-        ].
-
-        margin ~~ 0 ifTrue:[
-            mustRedrawBottomEdge := newHeight < height.
-            mustRedrawRightEdge := newWidth < width.
-            anyEdge := mustRedrawBottomEdge or:[mustRedrawRightEdge].
-
-            mustRedrawPreviousRightBorderArea := newWidth > width.
-            mustRedrawPreviousBottomBorderArea := newHeight > height.
-        ] ifFalse:[
-            anyEdge := mustRedrawPreviousRightBorderArea := mustRedrawPreviousBottomBorderArea := false
-        ].
-
-        mustRedrawPreviousRightBorderArea ifTrue:[
-            self invalidateDeviceRectangle:((width-margin)@0 extent:margin@height) repairNow:false.
-        ].
-        mustRedrawPreviousBottomBorderArea ifTrue:[
-            self invalidateDeviceRectangle:((0 @ (height-margin)) extent:width@margin) repairNow:false.
-        ].
-
-        width := newWidth.
-        height := newHeight.
-
-        "recompute inner-clip if needed"
-        self setInnerClip.
-
-        "
-         must first process pending exposes;
-         otherwise, those may be drawn at a wrong position
-        "
+	realized ifFalse:[
+	    width := newWidth.
+	    height := newHeight.
+	    self extentChangedFlag:true.
+	    ^ self
+	].
+
+	((newWidth <= width) and:[newHeight <= height]) ifTrue:[
+	    how := #smaller
+	] ifFalse:[
+	    ((newWidth >= width) and:[newHeight >= height]) ifTrue:[
+		how := #larger
+	    ]
+	].
+
+	margin ~~ 0 ifTrue:[
+	    mustRedrawBottomEdge := newHeight < height.
+	    mustRedrawRightEdge := newWidth < width.
+	    anyEdge := mustRedrawBottomEdge or:[mustRedrawRightEdge].
+
+	    mustRedrawPreviousRightBorderArea := newWidth > width.
+	    mustRedrawPreviousBottomBorderArea := newHeight > height.
+	] ifFalse:[
+	    anyEdge := mustRedrawPreviousRightBorderArea := mustRedrawPreviousBottomBorderArea := false
+	].
+
+	mustRedrawPreviousRightBorderArea ifTrue:[
+	    self invalidateDeviceRectangle:((width-margin)@0 extent:margin@height) repairNow:false.
+	].
+	mustRedrawPreviousBottomBorderArea ifTrue:[
+	    self invalidateDeviceRectangle:((0 @ (height-margin)) extent:width@margin) repairNow:false.
+	].
+
+	width := newWidth.
+	height := newHeight.
+
+	"recompute inner-clip if needed"
+	self setInnerClip.
+
+	"
+	 must first process pending exposes;
+	 otherwise, those may be drawn at a wrong position
+	"
 "/ claus: no; expose events are in the same queue as configure events;
 "/        which is exactly for that reason ...
 
 "/        windowGroup notNil ifTrue:[
 "/            windowGroup processExposeEvents
 "/        ].
-        self sizeChanged:how.
-
-        (anyEdge and:[shown]) ifTrue:[
-            mustRedrawBottomEdge ifTrue:[
-                self invalidateDeviceRectangle:((0 @ (height-margin)) extent:width@margin) repairNow:false.
-            ].
-            mustRedrawRightEdge ifTrue:[
-                self invalidateDeviceRectangle:((width-margin)@0 extent:margin@height) repairNow:false.
-            ].
+	self sizeChanged:how.
+
+	(anyEdge and:[shown]) ifTrue:[
+	    mustRedrawBottomEdge ifTrue:[
+		self invalidateDeviceRectangle:((0 @ (height-margin)) extent:width@margin) repairNow:false.
+	    ].
+	    mustRedrawRightEdge ifTrue:[
+		self invalidateDeviceRectangle:((width-margin)@0 extent:margin@height) repairNow:false.
+	    ].
 "/ OLD code:
 "/            self clippingRectangle:nil.
 "/            mustRedrawBottomEdge ifTrue:[
@@ -5937,11 +5942,11 @@
 "/                self drawRightEdge
 "/            ].
 "/            self deviceClippingRectangle:innerClipRect
-        ]
+	]
     ].
 
     originChanged ifTrue:[
-        dependents notNil ifTrue:[ self changed:#origin ].
+	dependents notNil ifTrue:[ self changed:#origin ].
     ].
 
     "Modified: / 10.10.2001 / 14:14:19 / cg"
@@ -5962,20 +5967,20 @@
      slowly migrating to use layoutObjects ...
     "
     layout isNil ifTrue:[
-        newOrg := self computeOrigin.
-        newExt := self computeExtent.
+	newOrg := self computeOrigin.
+	newExt := self computeExtent.
     ] ifFalse:[layout isAssociation ifTrue:[
-        layout key == #extent ifTrue:[
-            newOrg := 1@1.
-            newExt := layout value.
-        ] ifFalse:[
-            self shouldImplement.
-        ].
+	layout key == #extent ifTrue:[
+	    newOrg := 1@1.
+	    newExt := layout value.
+	] ifFalse:[
+	    self shouldImplement.
+	].
     ] ifFalse:[
-        r := (layout rectangleRelativeTo:(superView viewRectangle)
-                               preferred:[self preferredBounds]).
-        newOrg := r origin rounded.
-        newExt := r extent rounded.
+	r := (layout rectangleRelativeTo:(superView viewRectangle)
+			       preferred:[self preferredBounds]).
+	newOrg := r origin rounded.
+	newExt := r extent rounded.
 "/ newOrg printCR.
 "/ newExt printCR.
     ]].
@@ -6042,9 +6047,9 @@
     "/ my subviews (they remember this in the shown instVar)
 
     realized ifTrue:[
-        shown ifTrue:[
-            self unmapped
-        ]
+	shown ifTrue:[
+	    self unmapped
+	]
     ]
 
     "Modified: 30.5.1996 / 11:41:25 / cg"
@@ -6079,11 +6084,11 @@
     "view has been destroyed by someone else (usually window system)"
 
     shown ifTrue:[
-        shown := false.
-        dependents notNil ifTrue:[
-            self changed:#visibility.
+	shown := false.
+	dependents notNil ifTrue:[
+	    self changed:#visibility.
             self changed:#destroyed 
-        ].
+	].
     ].
     super destroyed
 
@@ -6098,17 +6103,17 @@
 
     (dropTypeSymbol == WindowEvent dropType_file
     or:[dropTypeSymbol == WindowEvent dropType_directory]) ifTrue:[
-        dropObjects := Array with:(DropObject newFile:dropValue)
+	dropObjects := Array with:(DropObject newFile:dropValue)
     ] ifFalse:[
-        dropTypeSymbol == WindowEvent dropType_files ifTrue:[
-           dropObjects := (dropValue collect:[:fn | DropObject newFile:fn])
-        ] ifFalse:[
-            dropTypeSymbol == WindowEvent dropType_text ifTrue:[
-               dropObjects := Array with:(DropObject newText:dropValue)
-            ] ifFalse:[
-               dropObjects := Array with:(DropObject new:dropValue)
-            ]
-        ]
+	dropTypeSymbol == WindowEvent dropType_files ifTrue:[
+	   dropObjects := (dropValue collect:[:fn | DropObject newFile:fn])
+	] ifFalse:[
+	    dropTypeSymbol == WindowEvent dropType_text ifTrue:[
+	       dropObjects := Array with:(DropObject newText:dropValue)
+	    ] ifFalse:[
+	       dropObjects := Array with:(DropObject new:dropValue)
+	    ]
+	]
     ].
 
 "/    Transcript showCR:'Drop:'.
@@ -6129,7 +6134,7 @@
     |leftEdge topEdge rightEdge botEdge anyEdge nx ny nw nh old oldPaint|
 
     shown ifFalse:[
-        ^ self
+	^ self
     ].
     "/ JV@2016-02-21: Double check to make sure GC is not already destroyed
     "/ to avoid 'attempt to draw to closed drawable. Not sure how this could 
@@ -6149,110 +6154,110 @@
      check if there is a need to draw an edge (i.e. if margin is hit)
     "
     (margin ~~ 0) ifTrue:[
-        |currentTransformation|
-
-        leftEdge := false.
-        topEdge := false.
-        rightEdge := false.
-        botEdge := false.
-        currentTransformation := gc transformation.
-        currentTransformation notNil ifTrue:[
-            "
-             need device coordinates for this test
-            "
-            nx := currentTransformation applyToX:nx.
-            ny := currentTransformation applyToY:ny.
-            nw := currentTransformation applyScaleX:nw.
-            nh := currentTransformation applyScaleY:nh.
-        ].
-        "
-         adjust expose rectangle, to exclude the margin.
-         Care for rounding errors ...
-        "
-        (nx class ~~ SmallInteger) ifTrue:[
-            old := nx.
-            nx := nx truncated.
-            nw := nw + (nx - old).
-        ].
-        (ny class ~~ SmallInteger) ifTrue:[
-            old := ny.
-            ny := ny truncated.
-            nh := nh + (ny - old).
-        ].
-        (nw class ~~ SmallInteger) ifTrue:[
-            nw := nw truncated + 1
-        ].
-        (nh class ~~ SmallInteger) ifTrue:[
-            nh := nh truncated + 1
-        ].
-
-        (nx < margin) ifTrue:[
-            old := nx.
-            nx := margin.
-            nw := nw - (nx - old).
-            leftEdge := anyEdge := true.
-        ].
-        ((nx + nw - 1) >= (width - margin)) ifTrue:[
-            nw := (width - margin - nx).
-            rightEdge := anyEdge := true.
-        ].
-        (ny < margin) ifTrue:[
-            old := ny.
-            ny := margin.
-            nh := nh - (ny - old).
-            topEdge := anyEdge := true.
-        ].
-        ((ny + nh - 1) >= (height - margin)) ifTrue:[
-            nh := (height - margin - ny).
-            botEdge := anyEdge := true.
-        ].
-        currentTransformation notNil ifTrue:[
-            "
-             need logical coordinates for redraw
-            "
-            nx := currentTransformation applyInverseToX:nx.
-            ny := currentTransformation applyInverseToY:ny.
-            nw := currentTransformation applyInverseScaleX:nw.
-            nh := currentTransformation applyInverseScaleY:nh.
-        ].
+	|currentTransformation|
+
+	leftEdge := false.
+	topEdge := false.
+	rightEdge := false.
+	botEdge := false.
+	currentTransformation := gc transformation.
+	currentTransformation notNil ifTrue:[
+	    "
+	     need device coordinates for this test
+	    "
+	    nx := currentTransformation applyToX:nx.
+	    ny := currentTransformation applyToY:ny.
+	    nw := currentTransformation applyScaleX:nw.
+	    nh := currentTransformation applyScaleY:nh.
+	].
+	"
+	 adjust expose rectangle, to exclude the margin.
+	 Care for rounding errors ...
+	"
+	(nx class ~~ SmallInteger) ifTrue:[
+	    old := nx.
+	    nx := nx truncated.
+	    nw := nw + (nx - old).
+	].
+	(ny class ~~ SmallInteger) ifTrue:[
+	    old := ny.
+	    ny := ny truncated.
+	    nh := nh + (ny - old).
+	].
+	(nw class ~~ SmallInteger) ifTrue:[
+	    nw := nw truncated + 1
+	].
+	(nh class ~~ SmallInteger) ifTrue:[
+	    nh := nh truncated + 1
+	].
+
+	(nx < margin) ifTrue:[
+	    old := nx.
+	    nx := margin.
+	    nw := nw - (nx - old).
+	    leftEdge := anyEdge := true.
+	].
+	((nx + nw - 1) >= (width - margin)) ifTrue:[
+	    nw := (width - margin - nx).
+	    rightEdge := anyEdge := true.
+	].
+	(ny < margin) ifTrue:[
+	    old := ny.
+	    ny := margin.
+	    nh := nh - (ny - old).
+	    topEdge := anyEdge := true.
+	].
+	((ny + nh - 1) >= (height - margin)) ifTrue:[
+	    nh := (height - margin - ny).
+	    botEdge := anyEdge := true.
+	].
+	currentTransformation notNil ifTrue:[
+	    "
+	     need logical coordinates for redraw
+	    "
+	    nx := currentTransformation applyInverseToX:nx.
+	    ny := currentTransformation applyInverseToY:ny.
+	    nw := currentTransformation applyInverseScaleX:nw.
+	    nh := currentTransformation applyInverseScaleY:nh.
+	].
     ].
 
     (nw > 0 and:[nh > 0]) ifTrue:[
-        "
-         redraw inside area
-        "
-        self
-            clippingBounds:(Rectangle left:nx top:ny width:nw height:nh);
-            redrawX:nx y:ny width:nw height:nh.
+	"
+	 redraw inside area
+	"
+	self
+	    clippingBounds:(Rectangle left:nx top:ny width:nw height:nh);
+	    redrawX:nx y:ny width:nw height:nh.
     ].
 
     "
      redraw edge(s)
     "
     anyEdge ifTrue:[
-        self clippingBounds:nil.
-        oldPaint := self paint.
-        border notNil ifTrue:[
-            border displayOn:self forDisplayBox:(Rectangle left:0 top:0 width:width height:height).
-        ] ifFalse:[
-            (topEdge and:[leftEdge and:[botEdge and:[rightEdge]]]) ifTrue:[
-                self drawEdges
-            ] ifFalse:[
-                topEdge ifTrue:[
-                    self drawTopEdge
-                ].
-                leftEdge ifTrue:[
-                    self drawLeftEdge
-                ].
-                botEdge ifTrue:[
-                    self drawBottomEdge
-                ].
-                rightEdge ifTrue:[
-                    self drawRightEdge
-                ]
-            ].
-        ].
-        self paint:oldPaint.
+	self clippingBounds:nil.
+	oldPaint := self paint.
+	border notNil ifTrue:[
+	    border displayOn:self forDisplayBox:(Rectangle left:0 top:0 width:width height:height).
+	] ifFalse:[
+	    (topEdge and:[leftEdge and:[botEdge and:[rightEdge]]]) ifTrue:[
+		self drawEdges
+	    ] ifFalse:[
+		topEdge ifTrue:[
+		    self drawTopEdge
+		].
+		leftEdge ifTrue:[
+		    self drawLeftEdge
+		].
+		botEdge ifTrue:[
+		    self drawBottomEdge
+		].
+		rightEdge ifTrue:[
+		    self drawRightEdge
+		]
+	    ].
+	].
+	self paint:oldPaint.
     ].
     gc deviceClippingBounds:innerClipRect.
 
@@ -6285,7 +6290,9 @@
      pass it to the corresponding one.
      Otherwise, forward it to the superview, if there is any."
 
-    <resource: #keyboard ( #Menu ) >
+    <resource: #keyboard ( #Menu 
+                           #ZoomIn #ZoomOut
+                           #ZoomInAll #ZoomOutAll) >
 
     |focusView|
 
@@ -6309,6 +6316,15 @@
 	^ self activateMenu.
     ].
 
+    (key == #ZoomIn or:[key == #ZoomOut]) ifTrue:[ 
+        self keyboardZoom:(key == #ZoomIn).
+        ^ self
+    ].
+    (key == #ZoomInAll or:[key == #ZoomOutAll]) ifTrue:[ 
+        self keyboardZoomInAllViews:(key == #ZoomInAll).
+        ^ self
+    ].
+
     x isNil ifTrue:[
 	"/ already redelegated, but nowhere handled
 	superView notNil ifTrue:[
@@ -6357,7 +6373,16 @@
     "CTRL+/- action.
      ignored here - redefined in views which can zoom"
 
-"/    self changeScaleForMouseWheelZoom:amount
+    "/ self changeScaleForMouseWheelZoom:amount
+!
+
+keyboardZoomInAllViews:larger 
+    "CTRL+/- zoom action global.
+     Sent to all windows; some may ignore it."
+
+    self device allViewsDo:[:each |
+        each keyboardZoom:larger 
+    ].    
 !
 
 mapped
@@ -6369,9 +6394,9 @@
     "
      the old code was:
 
-        realized := true.
-        shown := true.
-        ...
+	realized := true.
+	shown := true.
+	...
 
      this created a race condition, if the view was
      realized and shortly after unrealized - before the mapped event
@@ -6381,41 +6406,41 @@
     "
 
     realized ifTrue:[
-        shownBefore := shown.
-
-        "/ currently, the 'shown ifFalse:' optimization is
-        "/ not ok, since 'shown' is also modified by visibilityChanges.
-        "/ Also, when remapped, X11 only sends a mapped event for the topView.
-        "/ Therefore, synthetically generate those #superViewMapped messages
-        "/ in any case.
-
-        shown := true.
-        "
-         backed views will not get expose events - have
-         to force a redraw here to get things drawn into
-         backing store.
-        "
-        backed ifTrue:[
-            self redrawX:0 y:0 width:width height:height
-        ].
-
-        "/ tell my subViews ...
-        subViews notNil ifTrue:[
+	shownBefore := shown.
+
+	"/ currently, the 'shown ifFalse:' optimization is
+	"/ not ok, since 'shown' is also modified by visibilityChanges.
+	"/ Also, when remapped, X11 only sends a mapped event for the topView.
+	"/ Therefore, synthetically generate those #superViewMapped messages
+	"/ in any case.
+
+	shown := true.
+	"
+	 backed views will not get expose events - have
+	 to force a redraw here to get things drawn into
+	 backing store.
+	"
+	backed ifTrue:[
+	    self redrawX:0 y:0 width:width height:height
+	].
+
+	"/ tell my subViews ...
+	subViews notNil ifTrue:[
             subViews do:[:v | 
 "/                v shown ifFalse:[
-                    v  mapped.
+		    v  mapped.
 "/                ]
-            ]
-        ].
-        shownBefore ~~ true ifTrue:[
-            dependents notNil ifTrue:[ self changed:#visibility ].
-        ].
-        self takeFocusWhenMapped ifTrue:[
-            "/ this is a one-shot!!
-            self takeFocusWhenMapped:false.
-            self assignKeyboardFocusToFirstKeyboardConsumer.
-            "/ self requestFocus
-        ].
+	    ]
+	].
+	shownBefore ~~ true ifTrue:[
+	    dependents notNil ifTrue:[ self changed:#visibility ].
+	].
+	self takeFocusWhenMapped ifTrue:[
+	    "/ this is a one-shot!!
+	    self takeFocusWhenMapped:false.
+	    self assignKeyboardFocusToFirstKeyboardConsumer.
+	    "/ self requestFocus
+	].
     ]
 
     "Modified: / 09-12-2010 / 18:12:24 / cg"
@@ -6444,29 +6469,29 @@
 
     horizontal := pageScroll := false.
     (UserPreferences current shiftMouseWheelScrollsHorizontally) ifTrue:[
-        horizontal := sensor shiftDown
+	horizontal := sensor shiftDown
     ] ifFalse:[                              
-        pageScroll := sensor shiftDown.
+	pageScroll := sensor shiftDown.
     ].
     
     pageScroll ifFalse:[
         amountToScroll := horizontal 
-                            ifTrue:[ self horizontalScrollStep]
-                            ifFalse:[ self verticalScrollStep ].
-        amountToScroll := self scaleMouseWheelScrollAmount:amountToScroll.
+			    ifTrue:[ self horizontalScrollStep]
+			    ifFalse:[ self verticalScrollStep ].
+	amountToScroll := self scaleMouseWheelScrollAmount:amountToScroll.
     ].
 
     amount > 0 ifTrue:[
 	pageScroll ifTrue:[
-            horizontal ifTrue:[self pageLeft] ifFalse:[self pageUp]
+	    horizontal ifTrue:[self pageLeft] ifFalse:[self pageUp]
 	] ifFalse:[
-            horizontal ifTrue:[self scrollLeft:amountToScroll] ifFalse:[self scrollUp:amountToScroll]
+	    horizontal ifTrue:[self scrollLeft:amountToScroll] ifFalse:[self scrollUp:amountToScroll]
 	]
     ] ifFalse:[
 	pageScroll ifTrue:[
-            horizontal ifTrue:[self pageRight] ifFalse:[self pageDown]
+	    horizontal ifTrue:[self pageRight] ifFalse:[self pageDown]
 	] ifFalse:[
-            horizontal ifTrue:[self scrollRight:amountToScroll] ifFalse:[self scrollDown:amountToScroll]
+	    horizontal ifTrue:[self scrollRight:amountToScroll] ifFalse:[self scrollDown:amountToScroll]
 	]
     ].
 
@@ -6487,18 +6512,18 @@
 
     "/ first ask my flags if its enforced or forbidden
     self requestFocusOnPointerEnter ifTrue:[
-        doRequestFocus := true
+	doRequestFocus := true
     ] ifFalse:[
-        self doNotRequestFocusOnPointerEnter ifTrue:[
-            doRequestFocus := false
-        ] ifFalse:[
-            "/ then look for the settings.
-            doRequestFocus := self wantsFocusWithPointerEnter
-        ]
+	self doNotRequestFocusOnPointerEnter ifTrue:[
+	    doRequestFocus := false
+	] ifFalse:[
+	    "/ then look for the settings.
+	    doRequestFocus := self wantsFocusWithPointerEnter
+	]
     ].
 
     doRequestFocus ifTrue:[
-        self requestFocus.
+	self requestFocus.
     ].
     dependents notNil ifTrue:[ self changed:#pointerInView ]
     
@@ -6578,12 +6603,12 @@
     |subViews|
 
     viewBackground isViewBackground ifTrue:[
-        "/ there is only one, which needs this: a gradient over the actual height/width;
-        "/ this cannot just fill the new exposed area, but must recompute the gradient scales
-        (viewBackground needsFullRedrawOnChangeOfWidth
-        or:[ viewBackground needsFullRedrawOnChangeOfHeight]) ifTrue:[
-            self invalidate
-        ]
+	"/ there is only one, which needs this: a gradient over the actual height/width;
+	"/ this cannot just fill the new exposed area, but must recompute the gradient scales
+	(viewBackground needsFullRedrawOnChangeOfWidth
+	or:[ viewBackground needsFullRedrawOnChangeOfHeight]) ifTrue:[
+	    self invalidate
+	]
     ].    
 
     (subViews := self subViews) notEmptyOrNil ifTrue:[
@@ -6676,20 +6701,20 @@
     |wdgr|
 
     shown ifTrue:[
-        shown := false.
-        dependents notNil ifTrue:[ self changed:#visibility ].
+	shown := false.
+	dependents notNil ifTrue:[ self changed:#visibility ].
     ].
     (wdgr := self windowGroup) notNil ifTrue:[
-        wdgr focusView == self ifTrue:[
-            wdgr focusViewUnmapped.
-        ].
+	wdgr focusView == self ifTrue:[
+	    wdgr focusViewUnmapped.
+	].
     ].
 
     subViews notNil ifTrue:[
-        subViews do:[:v |
-            v containerUnmapped
-        ].
-        dependents notNil ifTrue:[ self changed:#visibility ].
+	subViews do:[:v |
+	    v containerUnmapped
+	].
+	dependents notNil ifTrue:[ self changed:#visibility ].
     ]
 
     "Modified: 25.2.1997 / 22:40:52 / cg"
@@ -6704,8 +6729,8 @@
 
     newShown := how ~~ #fullyObscured.
     newShown ~~ shown ifTrue:[
-        shown := newShown.
-        dependents notNil ifTrue:[ self changed:#visibility ].
+	shown := newShown.
+	dependents notNil ifTrue:[ self changed:#visibility ].
     ].
 !
 
@@ -6902,13 +6927,13 @@
     |sequence ev lastView|
 
     (keyOrStringOrSymbol isCharacter or:[keyOrStringOrSymbol isSymbol])
-        ifTrue:[ sequence := Array with:keyOrStringOrSymbol ]
-        ifFalse:[ sequence := keyOrStringOrSymbol ].
+	ifTrue:[ sequence := Array with:keyOrStringOrSymbol ]
+	ifFalse:[ sequence := keyOrStringOrSymbol ].
 
     sequence do:[:each |
-        ev := WindowEvent keyPress:each x:0 y:0 view:self.
-        "/ x/y will be set in simulateUserEvent:ev at:aPoint
-        lastView := self simulateUserEvent:ev at:aPoint sendDisplayEvent:sendDisplayEvent
+	ev := WindowEvent keyPress:each x:0 y:0 view:self.
+	"/ x/y will be set in simulateUserEvent:ev at:aPoint
+	lastView := self simulateUserEvent:ev at:aPoint sendDisplayEvent:sendDisplayEvent
     ].
     ^ lastView
 !
@@ -6929,17 +6954,17 @@
     |sequence ev1 ev2 lastView|
 
     (keyOrStringOrSymbol isCharacter or:[keyOrStringOrSymbol isSymbol])
-        ifTrue:[ sequence := Array with:keyOrStringOrSymbol ]
-        ifFalse:[ sequence := keyOrStringOrSymbol ].
+	ifTrue:[ sequence := Array with:keyOrStringOrSymbol ]
+	ifFalse:[ sequence := keyOrStringOrSymbol ].
 
     sequence do:[:each |
-        ev1 := WindowEvent keyPress:each x:0 y:0 view:self.
-        "/ x/y will be set in simulateUserEvent:ev at:aPoint
-        lastView := self simulateUserEvent:ev1 at:aPoint sendDisplayEvent:sendDisplayEvent.
-
-        ev2 := WindowEvent keyRelease:each x:0 y:0 view:self.
-        "/ x/y will be set in simulateUserEvent:ev at:aPoint
-        lastView := self simulateUserEvent:ev2 at:aPoint sendDisplayEvent:sendDisplayEvent.
+	ev1 := WindowEvent keyPress:each x:0 y:0 view:self.
+	"/ x/y will be set in simulateUserEvent:ev at:aPoint
+	lastView := self simulateUserEvent:ev1 at:aPoint sendDisplayEvent:sendDisplayEvent.
+
+	ev2 := WindowEvent keyRelease:each x:0 y:0 view:self.
+	"/ x/y will be set in simulateUserEvent:ev at:aPoint
+	lastView := self simulateUserEvent:ev2 at:aPoint sendDisplayEvent:sendDisplayEvent.
     ].
     ^ lastView
 !
@@ -6960,13 +6985,13 @@
     |sequence ev lastView|
 
     (keyOrStringOrSymbol isCharacter or:[keyOrStringOrSymbol isSymbol])
-        ifTrue:[ sequence := Array with:keyOrStringOrSymbol ]
-        ifFalse:[ sequence := keyOrStringOrSymbol ].
+	ifTrue:[ sequence := Array with:keyOrStringOrSymbol ]
+	ifFalse:[ sequence := keyOrStringOrSymbol ].
 
     sequence do:[:each |
-        ev := WindowEvent keyRelease:each x:0 y:0 view:self.
-        "/ x/y will be set in simulateUserEvent:ev at:aPoint
-        lastView := self simulateUserEvent:ev at:aPoint sendDisplayEvent:sendDisplayEvent
+	ev := WindowEvent keyRelease:each x:0 y:0 view:self.
+	"/ x/y will be set in simulateUserEvent:ev at:aPoint
+	lastView := self simulateUserEvent:ev at:aPoint sendDisplayEvent:sendDisplayEvent
     ].
     ^ lastView
 !
@@ -7000,45 +7025,45 @@
     |targetView pointXLated|
 
     sendDisplayEvent ifTrue:[
-        "/ translate to screen coordinates
-        pointXLated := device translatePoint:aPoint from:(self id) to:(device rootWindowId).
-        device
-            sendKeyOrButtonEvent:ev type
-            x:pointXLated x y:pointXLated y
-            keyOrButton:(ev isKeyEvent ifTrue:[ev rawKey] ifFalse:[ev button])
-            state:(ev modifierFlags)
-            toViewId:self id.
-        ^ self.
+	"/ translate to screen coordinates
+	pointXLated := device translatePoint:aPoint from:(self id) to:(device rootWindowId).
+	device
+	    sendKeyOrButtonEvent:ev type
+	    x:pointXLated x y:pointXLated y
+	    keyOrButton:(ev isKeyEvent ifTrue:[ev rawKey] ifFalse:[ev button])
+	    state:(ev modifierFlags)
+	    toViewId:self id.
+	^ self.
     ].
 
     (ev isButtonEvent or:[ev isPointerEnterLeaveEvent]) ifTrue:[
-        "/ if there is a pointer grab, the event has to sent to that one
+	"/ if there is a pointer grab, the event has to sent to that one
         targetView := self device activePointerGrab.
     ] ifFalse:[
-        (ev isKeyEvent) ifTrue:[
-            "/ if there is a pointer grab, the event has to sent to that one
+	(ev isKeyEvent) ifTrue:[
+	    "/ if there is a pointer grab, the event has to sent to that one
             targetView := self device activeKeyboardGrab.
-        ].
+	].
     ].
     targetView isNil ifTrue:[
-        ((0@0 corner:self extent) containsPoint:aPoint) ifTrue:[
-            self subViews do:[:each |
-                |whichView|
-
-                whichView := each simulateUserEvent:ev at:(device translatePoint:aPoint fromView:self toView:each).
-                whichView notNil ifTrue:[^ whichView].
-            ].
-            targetView := self.
-        ].
+	((0@0 corner:self extent) containsPoint:aPoint) ifTrue:[
+	    self subViews do:[:each |
+		|whichView|
+
+		whichView := each simulateUserEvent:ev at:(device translatePoint:aPoint fromView:self toView:each).
+		whichView notNil ifTrue:[^ whichView].
+	    ].
+	    targetView := self.
+	].
     ].
 
     targetView notNil ifTrue:[
-        pointXLated := device translatePoint:aPoint fromView:self toView:targetView.
-        ev x:(pointXLated x).
-        ev y:(pointXLated y).
-        ev view:targetView.
-        targetView sensor pushEvent:ev.
-        ^ targetView
+	pointXLated := device translatePoint:aPoint fromView:self toView:targetView.
+	ev x:(pointXLated x).
+	ev y:(pointXLated y).
+	ev view:targetView.
+	targetView sensor pushEvent:ev.
+	^ targetView
     ].
 
     ^ nil
@@ -7055,13 +7080,13 @@
 
     self stopButtonLongPressedHandlerProcess.
     p :=
-        [
-            Delay waitForSeconds:0.7.
-            self sensor leftButtonPressed ifTrue:[
-                "/ simulate a right-button press
-                self buttonPress:2 x:0 y:0
-            ]
-        ] newProcess.
+	[
+	    Delay waitForSeconds:0.7.
+	    self sensor leftButtonPressed ifTrue:[
+		"/ simulate a right-button press
+		self buttonPress:2 x:0 y:0
+	    ]
+	] newProcess.
 
     device buttonLongPressedHandlerProcess:p.
     p resume.
@@ -7074,8 +7099,8 @@
 
     (p := device buttonLongPressedHandlerProcess) notNil ifTrue:[
 "/ Transcript showCR:'stop'.
-        device buttonLongPressedHandlerProcess:nil.
-        p terminate.
+	device buttonLongPressedHandlerProcess:nil.
+	p terminate.
     ].
 ! !
 
@@ -7086,13 +7111,13 @@
 
     wg := self windowGroup.
     wg notNil ifTrue:[
-        device isWindowsPlatform ifTrue:[
-            wg focusView:aConsumer byTab:true.
-        ] ifFalse:[
-            aConsumer requestFocus.
-            "/ consumer requestFocus. - could be denied; but we force it here
-            wg focusView:aConsumer byTab:false.
-        ].
+	device isWindowsPlatform ifTrue:[
+	    wg focusView:aConsumer byTab:true.
+	] ifFalse:[
+	    aConsumer requestFocus.
+	    "/ consumer requestFocus. - could be denied; but we force it here
+	    wg focusView:aConsumer byTab:false.
+	].
     ].
 !
 
@@ -7113,25 +7138,25 @@
     |firstInputField firstConsumer firstCursorConsumer consumer|
 
     self withAllSubViewsDo:[:v |
-        v shown ifTrue:[
-            (firstInputField isNil and:[v isInputField]) ifTrue:[
-                firstInputField := v
-            ].
-            (firstConsumer isNil and:[v isKeyboardConsumer]) ifTrue:[
-                firstConsumer := v
-            ].
-            (firstCursorConsumer isNil and:[v isCursorKeyConsumer]) ifTrue:[
-                firstCursorConsumer := v
-            ].
-        ].
+	v shown ifTrue:[
+	    (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 notNil and:[self preferFirstInputFieldWhenAssigningInitialFocus]) ifTrue:[
-        consumer := firstInputField.
+	consumer := firstInputField.
     ].
     consumer := (consumer ? firstConsumer ? firstCursorConsumer).
     "/ Transcript showCR:consumer.
     consumer notNil ifTrue:[
-        self assignKeyboardFocusTo:consumer
+	self assignKeyboardFocusTo:consumer
     ].
 
     "Modified: / 29-08-2006 / 14:32:30 / cg"
@@ -7356,7 +7381,7 @@
 	and:[superView notNil
 	and:[styleSheet notNil]]) ifTrue:[
 	    (styleSheet at:#'focus.showBorder' default:true) ifTrue:[
-                graphicsDevice := device.
+		graphicsDevice := device.
 
 		(graphicsDevice supportsWindowBorder:(bd := DefaultFocusBorderWidth)) ifFalse:[
 		    (graphicsDevice supportsWindowBorder:(bd := 1)) ifFalse:[
@@ -7400,7 +7425,7 @@
     explicit ifTrue:[
 	(self drawableId notNil and:[superView notNil]) ifTrue:[
 	    (styleSheet at:#'focus.showBorder' default:true) ifTrue:[
-                graphicsDevice := device.
+		graphicsDevice := device.
 
 		(graphicsDevice supportsWindowBorder:(bd := self borderWidth)) ifFalse:[
 		    (graphicsDevice supportsWindowBorder:(bd := 1)) ifFalse:[
@@ -7542,8 +7567,8 @@
 "/        sensor flushMotionEventsFor:nil
 "/    ].
     aCursorOrNil notNil ifTrue:[
-        cursor := (aCursorOrNil onDevice:device).
-        ^ device grabPointerInView:self withCursor:cursor
+	cursor := (aCursorOrNil onDevice:device).
+	^ device grabPointerInView:self withCursor:cursor
     ].
     ^ device grabPointerInView:self
 !
@@ -7554,14 +7579,14 @@
     |sensor|
 
     device activeKeyboardGrab == self ifTrue:[
-        (sensor := self sensor) notNil ifTrue:[
-            "/ make certain all X events have been received
-            device sync.
-            "/ now all events have been received.
-            "/ now, flush all pointer events
-            sensor flushKeyboardFor:self
-        ].
-        device ungrabKeyboard.
+	(sensor := self sensor) notNil ifTrue:[
+	    "/ make certain all X events have been received
+	    device sync.
+	    "/ now all events have been received.
+	    "/ now, flush all pointer events
+	    sensor flushKeyboardFor:self
+	].
+	device ungrabKeyboard.
     ].
 !
 
@@ -7571,14 +7596,14 @@
     |sensor|
 
     device activePointerGrab == self ifTrue:[
-        (sensor := self sensor) notNil ifTrue:[
-            "/ make certain all X events have been received
-            device sync.
-            "/ now all events have been received.
-            "/ now, flush all pointer events
-            sensor flushMotionEventsFor:self
-        ].
-        device ungrabPointer.
+	(sensor := self sensor) notNil ifTrue:[
+	    "/ make certain all X events have been received
+	    device sync.
+	    "/ now all events have been received.
+	    "/ now, flush all pointer events
+	    sensor flushMotionEventsFor:self
+	].
+	device ungrabPointer.
     ]
 ! !
 
@@ -7595,7 +7620,7 @@
     |app|
 
     (app := self application) notNil ifTrue:[
-        app noticeOfWindowClose:self
+	app noticeOfWindowClose:self
     ].
 !
 
@@ -7603,7 +7628,7 @@
     |app|
 
     (app := self application) notNil ifTrue:[
-        app noticeOfWindowOpen:self
+	app noticeOfWindowOpen:self
     ].
     dependents notNil ifTrue:[ self changed:#opened ] 
 !
@@ -7654,11 +7679,11 @@
 
     self isBeingDestroyed:true.
     realized ifTrue:[
-        self unmap.
+	self unmap.
     ].
     shown ifTrue:[
-        shown := false.
-        dependents notNil ifTrue:[ self changed:#visibility ].
+	shown := false.
+	dependents notNil ifTrue:[ self changed:#visibility ].
     ].
 
 "/    controller notNil ifTrue:[
@@ -7667,11 +7692,11 @@
 "/    ].
 
     subViews notNil ifTrue:[
-        self destroySubViews.
+	self destroySubViews.
     ].
     superView notNil ifTrue:[
-        superView removeSubView:self.
-        superView := nil
+	superView removeSubView:self.
+	superView := nil
     ].
     super destroy.
 
@@ -7683,13 +7708,13 @@
 "/    ].
 
     controller notNil ifTrue:[
-        controller release.
-        controller := nil.
+	controller release.
+	controller := nil.
     ].
 
     windowGroup notNil ifTrue:[
-        windowGroup removeView:self.
-        windowGroup := nil
+	windowGroup removeView:self.
+	windowGroup := nil
     ].
 
     self noticeOfWindowClose.
@@ -7710,32 +7735,32 @@
     viewBackground := DefaultViewBackgroundColor.
 
     DefaultLightColor notNil ifTrue:[
-        lightColor := DefaultLightColor.
+	lightColor := DefaultLightColor.
     ] ifFalse:[
-        device hasGrayscales ifTrue:[
-            (viewBackground isImageOrForm and:[viewBackground colorMap isNil]) ifTrue:[
-                lightColor := viewBackground averageColor lightened.
-            ] ifFalse:[
-                lightColor := viewBackground lightened.
-            ].
-            DefaultLightColor := lightColor.
-        ] ifFalse:[
-            "
-             this seems strange: on B&W screens, we create the light color
-             darker than normal viewBackground (White) -
-             to make the boundary of the view visible
-            "
-            lightColor := Color gray:50
-        ]
+	device hasGrayscales ifTrue:[
+	    (viewBackground isImageOrForm and:[viewBackground colorMap isNil]) ifTrue:[
+		lightColor := viewBackground averageColor lightened.
+	    ] ifFalse:[
+		lightColor := viewBackground lightened.
+	    ].
+	    DefaultLightColor := lightColor.
+	] ifFalse:[
+	    "
+	     this seems strange: on B&W screens, we create the light color
+	     darker than normal viewBackground (White) -
+	     to make the boundary of the view visible
+	    "
+	    lightColor := Color gray:50
+	]
     ].
     DefaultShadowColor notNil ifTrue:[
-        shadowColor := DefaultShadowColor.
+	shadowColor := DefaultShadowColor.
     ] ifFalse:[
-        shadowColor := self blackColor.
+	shadowColor := self blackColor.
     ].
 
     ((DefaultBorderWidth ? 1) ~= 0 and:[DefaultBorderColor notNil]) ifTrue:[
-        self border:(SimpleBorder width:(DefaultBorderWidth ? 1) color:DefaultBorderColor)
+	self border:(SimpleBorder width:(DefaultBorderWidth ? 1) color:DefaultBorderColor)
     ].
 
     "/ font := self defaultFont.  -- already done in #initialize
@@ -7783,7 +7808,6 @@
     self basicFont:self defaultFont.
 
     shown := realized := false.
-    "/ hiddenOnRealize := false.
     "/ explicitExtent := false.
 
     "fill in some defaults - some of them are usually redefined in subclasses
@@ -7853,9 +7877,9 @@
     self initStyle.
     (self drawableId notNil and:[self gcId notNil]) ifTrue:[
 	"force a change"
-        self border:oldBorder.
-        self level:oldLevel.
-        self viewBackground:self viewBackground.
+	self border:oldBorder.
+	self level:oldLevel.
+	self viewBackground:self viewBackground.
 	self clearView.
 	self invalidate.
     ].
@@ -7870,16 +7894,16 @@
 
     "if I have already been reinited - return"
     self drawableId notNil ifTrue:[
-        ^ self
+	^ self
     ].
 
     "
      superView must be there, first
     "
     superView notNil ifTrue:[
-        (sv := superView view) id isNil ifTrue:[
-            sv reinitialize
-        ]
+	(sv := superView view) id isNil ifTrue:[
+	    sv reinitialize
+	]
     ].
 
     "reinit cursor"
@@ -7891,18 +7915,18 @@
 
     "if I was mapped, do it again"
     realized ifTrue:[
-        "only remap if I have a superview - otherwise, I might be
-         a hidden iconView or menu ..."
-        superView notNil ifTrue:[
+	"only remap if I have a superview - otherwise, I might be
+	 a hidden iconView or menu ..."
+	superView notNil ifTrue:[
 "/            shown ifTrue:[
-            device
-                moveResizeWindow:self drawableId x:left y:top width:width height:height;
-                mapWindow:self drawableId
+	    device
+		moveResizeWindow:self drawableId x:left y:top width:width height:height;
+		mapWindow:self drawableId
 "/                mapView:self id:self drawableId iconified:false
 "/                atX:left y:top width:width height:height
 "/                minExtent:(self minExtent) maxExtent:(self maxExtent)
 "/            ].
-        ].
+	].
     ].
 
     "restore controller"
@@ -8108,8 +8132,8 @@
     font := gc font.
     oldSize := font size.
     newFont := font asSize:(largerBoolean
-                            ifTrue:[(oldSize + 1) min:100]
-                            ifFalse:[(oldSize-1) max:4]).
+			    ifTrue:[(oldSize + 1) min:100]
+			    ifFalse:[(oldSize-1) max:4]).
     self font:newFont.
 
     "Modified: / 27-02-1996 / 00:53:51 / cg"
@@ -8325,24 +8349,24 @@
 
     margin isNil ifTrue:[margin := 0].
     (margin ~~ 0) ifTrue:[
-        m2 := margin + margin.
-        nX := nY := margin.
-        nW := width - m2.
-        nH := height - m2.
+	m2 := margin + margin.
+	nX := nY := margin.
+	nW := width - m2.
+	nH := height - m2.
 "/        transformation notNil ifTrue:[
 "/            nX := transformation applyInverseToX:nX.
 "/            nY := transformation applyInverseToY:nY.
 "/            nW := transformation applyInverseScaleX:nW.
 "/            nH := transformation applyInverseScaleY:nH.
 "/        ].
-        innerClipRect := Rectangle
-                                 left:nX
-                                 top:nY
-                                 width:nW
-                                 height:nH
+	innerClipRect := Rectangle
+				 left:nX
+				 top:nY
+				 width:nW
+				 height:nH
     ] ifFalse:[
-        "no clipping"
-        innerClipRect := nil
+	"no clipping"
+	innerClipRect := nil
     ]
 
     "Modified: / 22.5.1999 / 16:50:58 / cg"
@@ -8401,17 +8425,17 @@
     |subViews|
 
     (subViews := self subViews) notNil ifTrue:[
-        subViews do:[:v| |p|
-            (ignoreInvisible or:[v shown]) ifTrue:[
-                (    (aPoint x between:(v left) and:(v right))
-                 and:[aPoint y between:(v top)  and:(v bottom)]
-                ) ifTrue:[
-                    "/ found a subview - the point is there
-                    p := device translatePoint:aPoint fromView:self toView:v.
-                    ^ v detectViewAt:p ignoreInvisible:ignoreInvisible.
-                ]
-            ]
-        ]
+	subViews do:[:v| |p|
+	    (ignoreInvisible or:[v shown]) ifTrue:[
+		(    (aPoint x between:(v left) and:(v right))
+		 and:[aPoint y between:(v top)  and:(v bottom)]
+		) ifTrue:[
+		    "/ found a subview - the point is there
+		    p := device translatePoint:aPoint fromView:self toView:v.
+		    ^ v detectViewAt:p ignoreInvisible:ignoreInvisible.
+		]
+	    ]
+	]
     ].
     "/ no subview - the point is here
     ^ self
@@ -8443,50 +8467,50 @@
     bw := self borderWidth ? 0.
 
     superView isNil ifTrue:[
-        inRect := 0@0 extent:device extent
+	inRect := 0@0 extent:device extent
     ] ifFalse:[
-        inRect := superView viewRectangle.
+	inRect := superView viewRectangle.
     ].
 
     bw2 := bw * 2.
 
     rel := aPoint x.
     rel isInteger ifFalse:[
-        newX := (rel * (inRect width + bw2)) asInteger + inRect left.
-        (bw ~~ 0) ifTrue:[
-            newX := newX - bw
-        ].
+	newX := (rel * (inRect width + bw2)) asInteger + inRect left.
+	(bw ~~ 0) ifTrue:[
+	    newX := newX - bw
+	].
     ] ifTrue:[
-        newX := rel
+	newX := rel
     ].
 
     rel := aPoint y.
     rel isInteger ifFalse:[
-        newY := (rel * (inRect height + bw2)) asInteger + inRect top.
-        (bw ~~ 0) ifTrue:[
-            newY := newY - bw
-        ].
+	newY := (rel * (inRect height + bw2)) asInteger + inRect top.
+	(bw ~~ 0) ifTrue:[
+	    newY := newY - bw
+	].
     ] ifTrue:[
-        newY := rel
+	newY := rel
     ].
 
     insets notNil ifTrue:[
-        i := insets at:1.   "top"
-        (i  ~~ 0) ifTrue:[
-            newX := newX - i
-        ].
-        i := insets at:3.   "left"
-        (i  ~~ 0) ifTrue:[
-            newX := newX - i
-        ].
-        i := insets at:2.   "right"
-        (i ~~ 0) ifTrue:[
-            newY := newY - i
-        ].
-        i := insets at:4.   "bottom"
-        (i ~~ 0) ifTrue:[
-            newY := newY - i
-        ].
+	i := insets at:1.   "top"
+	(i  ~~ 0) ifTrue:[
+	    newX := newX - i
+	].
+	i := insets at:3.   "left"
+	(i  ~~ 0) ifTrue:[
+	    newX := newX - i
+	].
+	i := insets at:2.   "right"
+	(i ~~ 0) ifTrue:[
+	    newY := newY - i
+	].
+	i := insets at:4.   "bottom"
+	(i ~~ 0) ifTrue:[
+	    newY := newY - i
+	].
     ].
     ^ newX @ newY
 !
@@ -8557,25 +8581,25 @@
     newLeft := origin x.
     newTop := origin y.
     ((newTop ~~ top) or:[newLeft ~~ left]) ifTrue:[
-        top := newTop.
-        left := newLeft.
-
-        "
-         if the receiver is visible, or is a topView, perform the
-         operation right away - otherwise, simply remember that the
-         origin has changed - will tell the display once we get realized
-        "
+	top := newTop.
+	left := newLeft.
+
+	"
+	 if the receiver is visible, or is a topView, perform the
+	 operation right away - otherwise, simply remember that the
+	 origin has changed - will tell the display once we get realized
+	"
 "/        (shown
 "/        or:[superView isNil and:[drawableId notNil]]) ifTrue:[
 
-        "/ no, have to do it if drawableId is there
-        "/ (otherwise, we could not move unmapped views around ...
-        "/
-        self drawableId notNil ifTrue:[
-            device moveWindow:self drawableId x:left y:top
-        ] ifFalse:[
-            self originChangedFlag:true
-        ]
+	"/ no, have to do it if drawableId is there
+	"/ (otherwise, we could not move unmapped views around ...
+	"/
+	self drawableId notNil ifTrue:[
+	    device moveWindow:self drawableId x:left y:top
+	] ifFalse:[
+	    self originChangedFlag:true
+	]
     ]
 
     "Modified: / 21-01-2011 / 13:59:08 / cg"
@@ -8612,16 +8636,16 @@
      a dimension <= 0 ... (although I think that 0 makes sense ...)
     "
     newWidth < 1 ifTrue:[
-        newWidth := 1.
+	newWidth := 1.
     ].
     newHeight < 1 ifTrue:[
-        newHeight := 1
+	newHeight := 1
     ].
 
     ((newWidth == width) and:[newHeight == height]) ifTrue:[
-        sameOrigin ifTrue:[^ self].
-        dependents notNil ifTrue:[ self changed:#origin ].
-        ^ self pixelOrigin:origin
+	sameOrigin ifTrue:[^ self].
+	dependents notNil ifTrue:[ self changed:#origin ].
+	^ self pixelOrigin:origin
     ].
 
     top := newTop.
@@ -8629,142 +8653,142 @@
 
 "/    shown ifTrue:[                  "4-nov-94 actually correct,"
     self drawableId notNil ifTrue:[        "but theres a bug in menus when resized while hidden"
-        mustRedrawBottomEdge := (margin ~~ 0) and:[newHeight < height].
-        mustRedrawRightEdge := (margin ~~ 0) and:[newWidth < width].
-
-        ((newHeight <= height) and:[newWidth <= width]) ifTrue:[
-            how := #smaller
-        ] ifFalse:[
-            ((newHeight >= height) and:[newWidth >= width]) ifTrue:[
-                how := #larger
-            ]
-        ].
-
-        mustRepaintRight := false.
-        mustRepaintBottom := false.
-
-        oldWidth := width.
-        oldHeight := height.
-
-        shown ifTrue:[
-            (margin ~~ 0) ifTrue:[
-                "clear the old edges"
-
-                oldPaint := nil.
-                newWidth > width ifTrue:[
-                    self clippingBounds:nil.
-                    oldPaint := self paint.
-                    self paint:viewBackground.
-                    self fillDeviceRectangleX:(width - margin)
-                                            y:0
-                                        width:margin
-                                       height:height.
-                    mustRepaintRight := true.
-                ].
-                newHeight > height ifTrue:[
-                    self clippingBounds:nil.
-                    oldPaint := self paint.
-                    self paint:viewBackground.
-                    self fillDeviceRectangleX:0
-                                            y:(height - margin)
-                                        width:width
-                                       height:margin.
-                    mustRepaintBottom := true.
-                ].
-                oldPaint notNil ifTrue:[ self paint:oldPaint. ]
-            ]
-        ].
-
-        width := newWidth.
-        height := newHeight.
-
-        self setInnerClip.
-
-        "if view becomes smaller, send sizeChanged first"
-        true  "(how == #smaller)" ifTrue:[
-            self sizeChanged:how
-        ].
-
-        "have to tell X, when extent of view is changed"
-        sameOrigin ifTrue:[
-            device resizeWindow:self drawableId width:width height:height.
-        ] ifFalse:[
-            "claus: some xservers seem to do better when resizing
-             first ...."
+	mustRedrawBottomEdge := (margin ~~ 0) and:[newHeight < height].
+	mustRedrawRightEdge := (margin ~~ 0) and:[newWidth < width].
+
+	((newHeight <= height) and:[newWidth <= width]) ifTrue:[
+	    how := #smaller
+	] ifFalse:[
+	    ((newHeight >= height) and:[newWidth >= width]) ifTrue:[
+		how := #larger
+	    ]
+	].
+
+	mustRepaintRight := false.
+	mustRepaintBottom := false.
+
+	oldWidth := width.
+	oldHeight := height.
+
+	shown ifTrue:[
+	    (margin ~~ 0) ifTrue:[
+		"clear the old edges"
+
+		oldPaint := nil.
+		newWidth > width ifTrue:[
+		    self clippingBounds:nil.
+		    oldPaint := self paint.
+		    self paint:viewBackground.
+		    self fillDeviceRectangleX:(width - margin)
+					    y:0
+					width:margin
+				       height:height.
+		    mustRepaintRight := true.
+		].
+		newHeight > height ifTrue:[
+		    self clippingBounds:nil.
+		    oldPaint := self paint.
+		    self paint:viewBackground.
+		    self fillDeviceRectangleX:0
+					    y:(height - margin)
+					width:width
+				       height:margin.
+		    mustRepaintBottom := true.
+		].
+		oldPaint notNil ifTrue:[ self paint:oldPaint. ]
+	    ]
+	].
+
+	width := newWidth.
+	height := newHeight.
+
+	self setInnerClip.
+
+	"if view becomes smaller, send sizeChanged first"
+	true  "(how == #smaller)" ifTrue:[
+	    self sizeChanged:how
+	].
+
+	"have to tell X, when extent of view is changed"
+	sameOrigin ifTrue:[
+	    device resizeWindow:self drawableId width:width height:height.
+	] ifFalse:[
+	    "claus: some xservers seem to do better when resizing
+	     first ...."
 "
-            (how == #smaller) ifTrue:[
-                device resizeWindow:drawableId width:width height:height.
-                device moveWindow:drawableId x:left y:top
-            ] ifFalse:[
-                device moveResizeWindow:drawableId x:left y:top width:width height:height
-            ].
+	    (how == #smaller) ifTrue:[
+		device resizeWindow:drawableId width:width height:height.
+		device moveWindow:drawableId x:left y:top
+	    ] ifFalse:[
+		device moveResizeWindow:drawableId x:left y:top width:width height:height
+	    ].
 "
-            device moveResizeWindow:self drawableId x:left y:top
-                                           width:width height:height.
-        ].
-
-        "if view becomes bigger, send sizeChanged after"
-        false "(how ~~ #smaller)" ifTrue:[
-            self sizeChanged:how
-        ].
-
-        shown ifTrue:[
-            (mustRedrawBottomEdge or:[mustRedrawRightEdge]) ifTrue:[
-                border notNil ifTrue:[
-                    mustRedrawBottomEdge ifTrue:[
-                        self invalidateDeviceRectangle:((0 @ (height - margin)) extent:width@margin) repairNow:false.
-                    ].
-                    mustRedrawRightEdge ifTrue:[
-                        self invalidateDeviceRectangle:(((width - margin) @ 0) extent:margin@height) repairNow:false.
-                    ].
-                ] ifFalse:[
-                    self deviceClippingBounds:nil.
-                    oldPaint := self paint.
-                    mustRedrawBottomEdge ifTrue:[
-                        self drawBottomEdge
-                    ].
-                    mustRedrawRightEdge ifTrue:[
-                        self drawRightEdge
-                    ].
-                    self paint:oldPaint.
-                    self deviceClippingBounds:innerClipRect
-                ]
-            ].
-        ].
-
-        mustRepaintRight ifTrue:[
-            self invalidateDeviceRectangle:(((oldWidth - margin) @ 0)
-                                           extent:margin@height)
-                                 repairNow:false.
+	    device moveResizeWindow:self drawableId x:left y:top
+					   width:width height:height.
+	].
+
+	"if view becomes bigger, send sizeChanged after"
+	false "(how ~~ #smaller)" ifTrue:[
+	    self sizeChanged:how
+	].
+
+	shown ifTrue:[
+	    (mustRedrawBottomEdge or:[mustRedrawRightEdge]) ifTrue:[
+		border notNil ifTrue:[
+		    mustRedrawBottomEdge ifTrue:[
+			self invalidateDeviceRectangle:((0 @ (height - margin)) extent:width@margin) repairNow:false.
+		    ].
+		    mustRedrawRightEdge ifTrue:[
+			self invalidateDeviceRectangle:(((width - margin) @ 0) extent:margin@height) repairNow:false.
+		    ].
+		] ifFalse:[
+		    self deviceClippingBounds:nil.
+		    oldPaint := self paint.
+		    mustRedrawBottomEdge ifTrue:[
+			self drawBottomEdge
+		    ].
+		    mustRedrawRightEdge ifTrue:[
+			self drawRightEdge
+		    ].
+		    self paint:oldPaint.
+		    self deviceClippingBounds:innerClipRect
+		]
+	    ].
+	].
+
+	mustRepaintRight ifTrue:[
+	    self invalidateDeviceRectangle:(((oldWidth - margin) @ 0)
+					   extent:margin@height)
+				 repairNow:false.
 "/            self redrawDeviceX:(oldWidth - margin)
 "/                             y:0
 "/                         width:margin
 "/                        height:height.
-        ].
-        mustRepaintBottom ifTrue:[
-            self invalidateDeviceRectangle:((0 @ (oldHeight - margin))
-                                           extent:width@margin)
-                                 repairNow:false.
+	].
+	mustRepaintBottom ifTrue:[
+	    self invalidateDeviceRectangle:((0 @ (oldHeight - margin))
+					   extent:width@margin)
+				 repairNow:false.
 "/            self redrawDeviceX:0
 "/                             y:(oldHeight - margin)
 "/                         width:width
 "/                        height:margin.
-        ].
+	].
     ] ifFalse:[
-        "otherwise memorize the need for a sizeChanged message"
-
-        width := newWidth.
-        height := newHeight.
-        sameOrigin ifFalse:[
-            self originChangedFlag:true.
-        ].
-        self extentChangedFlag:true.
-        subViews notEmptyOrNil ifTrue:[
-            self extentChangedBeforeCreatedFlag:true.
-        ].
+	"otherwise memorize the need for a sizeChanged message"
+
+	width := newWidth.
+	height := newHeight.
+	sameOrigin ifFalse:[
+	    self originChangedFlag:true.
+	].
+	self extentChangedFlag:true.
+	subViews notEmptyOrNil ifTrue:[
+	    self extentChangedBeforeCreatedFlag:true.
+	].
     ].
     sameOrigin ifFalse:[
-        dependents notNil ifTrue:[ self changed:#origin ].
+	dependents notNil ifTrue:[ self changed:#origin ].
     ].
 
     "Modified: / 25.5.1999 / 14:49:56 / cg"
@@ -8778,39 +8802,39 @@
     bw := self borderWidth ? 0.
 
     superView isNil ifTrue:[
-        superWidth := device width + bw.
-        superHeight := device height + bw.
-        superLeft := superTop := 0.
+	superWidth := device width + bw.
+	superHeight := device height + bw.
+	superLeft := superTop := 0.
     ] ifFalse:[
-        inRect := superView viewRectangle.
-        superWidth := inRect width.
-        superHeight := inRect height.
-        superLeft := inRect left.
-        superTop := inRect top.
+	inRect := superView viewRectangle.
+	superWidth := inRect width.
+	superHeight := inRect height.
+	superLeft := inRect left.
+	superTop := inRect top.
     ].
 
     rel := p x.
     rel isInteger ifTrue:[
-        newX := rel
+	newX := rel
     ] ifFalse:[
-        newX := (rel * superWidth) asInteger + superLeft.
-        (bw ~~ 0) ifTrue:[
-            rel ~= 1.0 ifTrue:[
-                newX := newX - bw
-            ]
-        ]
+	newX := (rel * superWidth) asInteger + superLeft.
+	(bw ~~ 0) ifTrue:[
+	    rel ~= 1.0 ifTrue:[
+		newX := newX - bw
+	    ]
+	]
     ].
 
     rel := p y.
     rel isInteger ifTrue:[
-        newY := rel
+	newY := rel
     ] ifFalse:[
-        newY := (rel * superHeight) asInteger + superTop.
-        (bw ~~ 0) ifTrue:[
-            rel ~= 1.0 ifTrue:[
-                newY := newY - bw
-            ]
-        ]
+	newY := (rel * superHeight) asInteger + superTop.
+	(bw ~~ 0) ifTrue:[
+	    rel ~= 1.0 ifTrue:[
+		newY := newY - bw
+	    ]
+	]
     ].
     ^ newX @ newY
 
@@ -8892,16 +8916,16 @@
     focusViewToCheck == self ifTrue:[ ^ true ].
 
     focusViewToCheck notNil ifTrue:[
-        (focusViewToCheck isComponentOf: self) ifTrue:[ ^ true ].
-
-        "mhmh - is there a delegation to me ?"
-        (delegate := focusViewToCheck delegate) notNil ifTrue:[
-            delegate == self ifTrue:[^ true].
-            "/ no: delegate does not understand this (EnterFieldGroup or KbdForwarder)
-            "/ we will see, if commenting this leads to problems...
-            "/ (delegate isComponentOf: self) ifTrue:[ ^ true ].
-            ^ delegate askFor:#delegatesTo: with:self
-        ]
+	(focusViewToCheck isComponentOf: self) ifTrue:[ ^ true ].
+
+	"mhmh - is there a delegation to me ?"
+	(delegate := focusViewToCheck delegate) notNil ifTrue:[
+	    delegate == self ifTrue:[^ true].
+	    "/ no: delegate does not understand this (EnterFieldGroup or KbdForwarder)
+	    "/ we will see, if commenting this leads to problems...
+	    "/ (delegate isComponentOf: self) ifTrue:[ ^ true ].
+	    ^ delegate askFor:#delegatesTo: with:self
+	]
     ].
     ^ false
 
@@ -9023,11 +9047,11 @@
     focusViewToCheck == self ifTrue:[ ^ true ].
 
     focusViewToCheck notNil ifTrue:[
-        "mhmh - is there a delegation to me ?"
-        (delegate := focusViewToCheck delegate) notNil ifTrue:[
-            delegate == self ifTrue:[^ true].
-            ^ delegate askFor:#delegatesTo: with:self
-        ]
+	"mhmh - is there a delegation to me ?"
+	(delegate := focusViewToCheck delegate) notNil ifTrue:[
+	    delegate == self ifTrue:[^ true].
+	    ^ delegate askFor:#delegatesTo: with:self
+	]
     ].
     ^ false
 
@@ -9393,7 +9417,7 @@
 
 buttonMotionEventPending
     "return true, if a button motion event is pending.
-     Normally, you dont want to use this, since no polling is needed
+     Normally, you don't want to use this, since no polling is needed
      (not even for mouse-tracking).
      Actually, its a historical leftover"
 
@@ -9496,11 +9520,11 @@
      This does not make the view visible (needs a #map for that)"
 
     self drawableId isNil ifTrue:[
-        "
-         make certain that superview is created also
-        "
-        superView notNil ifTrue:[
-             superView view create.
+	"
+	 make certain that superview is created also
+	"
+	superView notNil ifTrue:[
+	     superView view create.
 
 "/            "and put my controller into the superviews controller list"
 "/            controller notNil ifTrue:[
@@ -9508,43 +9532,43 @@
 "/                    controller manager:(superView controller manager)
 "/                ]
 "/            ]
-        ] ifFalse:[
-            device isNil ifTrue:[ device := Screen current ].
-            "/
-            "/ if the display is not already dispatching events,
-            "/ this starts the event process.
-            "/
-            device startDispatch
-        ].
-
-        cursor notNil ifTrue:[
-            cursor := cursor onDevice:device.
-        ].
-
-        self extentChangedBeforeCreatedFlag ifTrue:[
-            "/ this is true, if the extent was changed before
-            "/ this view was created (and therefore, no sizeChangeEvent
-            "/ was sent to me, which would notify children.)
-            "/ have to do this here.
-            self sizeChanged:nil.   "/ must tell children (if any)
-        ].
-        self hasExplicitExtent ifFalse:[
-            self resize
-        ].
-
-        self physicalCreate.
-
-        viewBackground notNil ifTrue:[
-           self setViewBackground
-        ].
-
-        self initEvents.
-
-        "
-         this is the first create,
-         force sizechange messages to be sent to the view
-        "
-        self originChangedFlag:true extentChangedFlag:true
+	] ifFalse:[
+	    device isNil ifTrue:[ device := Screen current ].
+	    "/
+	    "/ if the display is not already dispatching events,
+	    "/ this starts the event process.
+	    "/
+	    device startDispatch
+	].
+
+	cursor notNil ifTrue:[
+	    cursor := cursor onDevice:device.
+	].
+
+	self extentChangedBeforeCreatedFlag ifTrue:[
+	    "/ this is true, if the extent was changed before
+	    "/ this view was created (and therefore, no sizeChangeEvent
+	    "/ was sent to me, which would notify children.)
+	    "/ have to do this here.
+	    self sizeChanged:nil.   "/ must tell children (if any)
+	].
+	self hasExplicitExtent ifFalse:[
+	    self resize
+	].
+
+	self physicalCreate.
+
+	viewBackground notNil ifTrue:[
+	   self setViewBackground
+	].
+
+	self initEvents.
+
+	"
+	 this is the first create,
+	 force sizechange messages to be sent to the view
+	"
+	self originChangedFlag:true extentChangedFlag:true
     ]
 
     "Modified: 28.3.1997 / 13:50:17 / cg"
@@ -9571,10 +9595,10 @@
      is always sent."
     
     shadowColor notNil ifTrue:[
-        shadowColor := shadowColor onDevice:device
+	shadowColor := shadowColor onDevice:device
     ].
     lightColor notNil ifTrue:[
-        lightColor := lightColor onDevice:device
+	lightColor := lightColor onDevice:device
     ].
 
     "Created: 13.1.1997 / 21:51:59 / cg"
@@ -9593,25 +9617,25 @@
      slowly migrating to use layoutObjects ...
     "
     layout notNil ifTrue:[
-        superView notNil ifTrue:[
-            (self originOrExtentOrCornerChanged) ifTrue:[
-                layout isAssociation ifTrue:[
-                    layout key == #extent ifTrue:[
-                        org := 1@1.
-                        ext := layout value.
-                    ] ifFalse:[
-                        self shouldImplement.
-                    ].
-                ] ifFalse:[
-                    r := (layout rectangleRelativeTo:(superView viewRectangle)
-                                           preferred:[self preferredBounds]).
-                    org := r origin rounded.
-                    ext := r extent rounded.
-                ].
-                self pixelOrigin:org extent:ext.
-            ].
-        ].
-        ^ self.
+	superView notNil ifTrue:[
+	    (self originOrExtentOrCornerChanged) ifTrue:[
+		layout isAssociation ifTrue:[
+		    layout key == #extent ifTrue:[
+			org := 1@1.
+			ext := layout value.
+		    ] ifFalse:[
+			self shouldImplement.
+		    ].
+		] ifFalse:[
+		    r := (layout rectangleRelativeTo:(superView viewRectangle)
+					   preferred:[self preferredBounds]).
+		    org := r origin rounded.
+		    ext := r extent rounded.
+		].
+		self pixelOrigin:org extent:ext.
+	    ].
+	].
+	^ self.
     ].
 
     "if the extent is not the one we created the window with ..."
@@ -9623,20 +9647,20 @@
     self originChangedFlag ifTrue:[
 "/        org := self computeOrigin.
 "/        self pixelOrigin:org.
-        originRule notNil ifTrue:[
-            self pixelOrigin:self computeOrigin
-        ] ifFalse:[
-            relativeOrigin notNil ifTrue:[
-                self originFromRelativeOrigin:relativeOrigin
-            ] ifFalse:[
-                shown ifTrue:[
-                    device moveWindow:self drawableId x:left y:top.
-                ] ifFalse:[
-                    self pixelOrigin:left@top
-                ].
-            ].
-        ].
-        self originChangedFlag:false
+	originRule notNil ifTrue:[
+	    self pixelOrigin:self computeOrigin
+	] ifFalse:[
+	    relativeOrigin notNil ifTrue:[
+		self originFromRelativeOrigin:relativeOrigin
+	    ] ifFalse:[
+		shown ifTrue:[
+		    device moveWindow:self drawableId x:left y:top.
+		] ifFalse:[
+		    self pixelOrigin:left@top
+		].
+	    ].
+	].
+	self originChangedFlag:false
     ]
 
     "Modified: 18.6.1996 / 21:44:03 / cg"
@@ -9731,61 +9755,61 @@
      (unless you have a dictator as windowManager ;-).
      If the iconified argument is true, the window is created as icon initially.
      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'"
 
     |subs|
 
     realized ifFalse:[
-        self drawableId isNil ifTrue:[
-            "
-             first time ?
-             yes, realize (implies a map)
-            "
-            self realizeKeepingGroup:false at:aPoint iconified:iconified
-        ] ifFalse:[
-            "
-             no, map only
-            "
-            realized := true.
-            aPoint isNil ifTrue:[
-                iconified ifTrue:[
-                    device
-                        mapView:self id:self drawableId iconified:iconified
-                        atX:0 y:0
-                        width:width height:height
-                        minExtent:(self minExtent) maxExtent:(self maxExtent).
-                ] ifFalse:[
-                    device mapWindow:self drawableId.
-                ]
-            ] ifFalse:[
-                left := aPoint x.
-                top := aPoint y.
-                device
-                    mapView:self id:self drawableId iconified:iconified
-                    atX:left y:top
-                    width:width height:height
-                    minExtent:(self minExtent) maxExtent:(self maxExtent).
-            ].
-
-            "/
-            "/ implies that all realized subviews
-            "/ are now also mapped
-            "/
-            "/ not needed for topViews - the mapped event does exactly the same
-            "/ however, X does not generate mapped events for non-topViews
-            "/ when a view gets deiconified.
-
-            superView notNil ifTrue:[
-                (subs := self subViews) notNil ifTrue:[
-                    subs do:[:v |
-                        v realized "shown" ifFalse:[
-                            v mapped
-                        ]
-                    ]
-                ]
-            ]
-        ].
+	self drawableId isNil ifTrue:[
+	    "
+	     first time ?
+	     yes, realize (implies a map)
+	    "
+	    self realizeKeepingGroup:false at:aPoint iconified:iconified
+	] ifFalse:[
+	    "
+	     no, map only
+	    "
+	    realized := true.
+	    aPoint isNil ifTrue:[
+		iconified ifTrue:[
+		    device
+			mapView:self id:self drawableId iconified:iconified
+			atX:0 y:0
+			width:width height:height
+			minExtent:(self minExtent) maxExtent:(self maxExtent).
+		] ifFalse:[
+		    device mapWindow:self drawableId.
+		]
+	    ] ifFalse:[
+		left := aPoint x.
+		top := aPoint y.
+		device
+		    mapView:self id:self drawableId iconified:iconified
+		    atX:left y:top
+		    width:width height:height
+		    minExtent:(self minExtent) maxExtent:(self maxExtent).
+	    ].
+
+	    "/
+	    "/ implies that all realized subviews
+	    "/ are now also mapped
+	    "/
+	    "/ not needed for topViews - the mapped event does exactly the same
+	    "/ however, X does not generate mapped events for non-topViews
+	    "/ when a view gets deiconified.
+
+	    superView notNil ifTrue:[
+		(subs := self subViews) notNil ifTrue:[
+		    subs do:[:v |
+			v realized "shown" ifFalse:[
+			    v mapped
+			]
+		    ]
+		]
+	    ]
+	].
     ]
 
     "Modified: 23.8.1996 / 14:53:55 / stefan"
@@ -10034,8 +10058,7 @@
             self mapIconified
         ]
     ] ifFalse:[
-        (self isHiddenOnRealize not
-         and:[visibilityChannel isNil or:[visibilityChannel value]]) ifTrue:[
+        self isHiddenOnRealize ifFalse:[
             self setInnerClip.
 
             realized ifFalse:[
@@ -10068,22 +10091,22 @@
     self isBeingDestroyed ifTrue:[ ^self ].
 
     self drawableId isNil ifTrue:[
-        super recreate.
-        self physicalCreate.
-
-        viewBackground notNil ifTrue:[
-            self setViewBackground
-        ].
-
-        "
-         XXX has to be changed: eventmasks are device specific -
-         XXX will not allow restart on another Workstation-type.
-         XXX event masks must become symbolic
-        "
-        eventMask isNil ifTrue:[
-            eventMask := device defaultEventMask
-        ].
-        device setEventMask:eventMask in:self drawableId
+	super recreate.
+	self physicalCreate.
+
+	viewBackground notNil ifTrue:[
+	    self setViewBackground
+	].
+
+	"
+	 XXX has to be changed: eventmasks are device specific -
+	 XXX will not allow restart on another Workstation-type.
+	 XXX event masks must become symbolic
+	"
+	eventMask isNil ifTrue:[
+	    eventMask := device defaultEventMask
+	].
+	device setEventMask:eventMask in:self drawableId
     ]
 !
 
@@ -10091,16 +10114,16 @@
     "realize all my subviews and all of their subviews - but not myself."
 
     subViews notNil ifTrue:[
-        subViews do:[:subView |
-            subView realize.
-            subView recursiveRealizeAllSubViews.
-        ]
+	subViews do:[:subView |
+	    subView realize.
+	    subView recursiveRealizeAllSubViews.
+	]
     ].
     components notNil ifTrue:[
-        components do:[:component |
-            component realize.
-            component recursiveRealizeAllSubViews.
-        ]
+	components do:[:component |
+	    component realize.
+	    component recursiveRealizeAllSubViews.
+	]
     ].
 !
 
@@ -10111,18 +10134,18 @@
      are known to ignore this ..."
 
     realized ifFalse:[
-        self drawableId isNil ifTrue:[
-            self realize
-        ] ifFalse:[    
-            "
-             now, make the view visible
-            "
-            realized := true.
-            device
-                mapView:self id:self drawableId iconified:false
-                atX:left y:top width:width height:height
-                minExtent:(self minExtent) maxExtent:(self maxExtent)
-        ]
+	self drawableId isNil ifTrue:[
+	    self realize
+	] ifFalse:[
+	    "
+	     now, make the view visible
+	    "
+	    realized := true.
+	    device
+		mapView:self id:self drawableId iconified:false
+		atX:left y:top width:width height:height
+		minExtent:(self minExtent) maxExtent:(self maxExtent)
+	]
     ]
 
     "Created: 8.5.1996 / 09:33:06 / cg"
@@ -10163,17 +10186,17 @@
     "rerealize myself with all subviews"
 
     self drawableId notNil ifTrue:[
-        realized := true.
-        self realizeAllSubViews.
-        superView isNil ifTrue:[
-            device
-                mapView:self id:self drawableId iconified:false
-                atX:left y:top width:width height:height
-                minExtent:(self minExtent) maxExtent:(self maxExtent)
-        ] ifFalse:[
-            device
-                mapWindow:self drawableId
-        ].
+	realized := true.
+	self realizeAllSubViews.
+	superView isNil ifTrue:[
+	    device
+		mapView:self id:self drawableId iconified:false
+		atX:left y:top width:width height:height
+		minExtent:(self minExtent) maxExtent:(self maxExtent)
+	] ifFalse:[
+	    device
+		mapWindow:self drawableId
+	].
     ]
 
     "Modified: 28.1.1997 / 17:59:28 / cg"
@@ -10205,24 +10228,24 @@
     "unmap the view - the view stays created (but invisible), and can be remapped again later."
 
     realized ifTrue:[
-        realized := false.
-        self drawableId notNil ifTrue:[
-            device unmapWindow:self drawableId.
-
-            "/ make it go away immediately
-            "/ (this hides the subview killing)
-            self flush.
-        ].
-
-        "/ Normally, this is not correct with X, where the
-        "/ unmap is an asynchronous operation.
-        "/ (shown is cleared also in unmapped event)
-        "/ Do it anyway, to avoid synchronisation problems.
-
-        shown ifTrue:[
-            shown := false.
-            dependents notNil ifTrue:[ self changed:#visibility ].
-        ]
+	realized := false.
+	self drawableId notNil ifTrue:[
+	    device unmapWindow:self drawableId.
+
+	    "/ make it go away immediately
+	    "/ (this hides the subview killing)
+	    self flush.
+	].
+
+	"/ Normally, this is not correct with X, where the
+	"/ unmap is an asynchronous operation.
+	"/ (shown is cleared also in unmapped event)
+	"/ Do it anyway, to avoid synchronisation problems.
+
+	shown ifTrue:[
+	    shown := false.
+	    dependents notNil ifTrue:[ self changed:#visibility ].
+	]
     ].
 
     "
@@ -10232,9 +10255,9 @@
      top extent:200@200.
 
      sub := View
-                origin:0.2@0.2
-                corner:0.8@0.8
-                in:top.
+		origin:0.2@0.2
+		corner:0.8@0.8
+		in:top.
 
      sub viewBackground:Color red.
      sub hiddenOnRealize:true.
@@ -10333,16 +10356,16 @@
 
     self fill:flashColor.
     messageOrNil notNil ifTrue:[
-        self withForeground:self whiteColor do:[
-            self displayString:messageOrNil centeredAt:(self center).
-        ].
+	self withForeground:self whiteColor do:[
+	    self displayString:messageOrNil centeredAt:(self center).
+	].
     ].
     Delay waitForSeconds:0.1.
     self fill:self whiteColor.
     messageOrNil notNil ifTrue:[
-        self withForeground:self blackColor do:[
-            self displayString:messageOrNil centeredAt:(self center).
-        ].
+	self withForeground:self blackColor do:[
+	    self displayString:messageOrNil centeredAt:(self center).
+	].
     ].
     Delay waitForSeconds:0.1.
     self fill:viewBackground.
@@ -10376,13 +10399,13 @@
      until the receiver's windowGroupProcess gets rescheduled."
 
     shown ifFalse:[
-        "/ no need to add damage - will get a full-redraw anyway,
-        "/ when I will be shown again.
-        ^ self
+	"/ no need to add damage - will get a full-redraw anyway,
+	"/ when I will be shown again.
+	^ self
     ].
     self
-        invalidateDeviceRectangle:(Rectangle left:0 top:0 width:width height:height)
-        repairNow:false
+	invalidateDeviceRectangle:(Rectangle left:0 top:0 width:width height:height)
+	repairNow:false
 
     "Modified: / 9.11.1998 / 21:04:16 / cg"
 !
@@ -10397,9 +10420,9 @@
      intil the receiver's windowGroupProcess gets rescheduled."
 
     shown ifFalse:[
-        "/ no need to add damage - will get a full-redraw anyway,
-        "/ when I will be shown again.
-        ^ self
+	"/ no need to add damage - will get a full-redraw anyway,
+	"/ when I will be shown again.
+	^ self
     ].
     self invalidate:aRectangle repairNow:false
 
@@ -10500,7 +10523,7 @@
 redraw
     "redraw myself completely - this is sent by redrawX:y:width:height:
      as a fallback.
-     Cannot do much here - is redefined in subclasses which dont care for
+     Cannot do much here - is redefined in subclasses which don't care for
      updating regions but instead update everything."
 
     "Modified: 29.5.1996 / 18:02:52 / cg"
@@ -10569,7 +10592,7 @@
     self clippingBounds:area.
 
     self clearExposedAreaInRedraw ifTrue:[
-        self clearRectangleX:x y:y width:w height:h.
+	self clearRectangleX:x y:y width:w height:h.
     ].
 
     self renderOrRedraw.
@@ -10925,12 +10948,12 @@
     wCont := self widthOfContents.
     currentTransformation := gc transformation.
     currentTransformation isNil ifTrue:[
-        orgY := orgX := 0
+	orgY := orgX := 0
     ] ifFalse:[
-        wCont := (currentTransformation applyScaleX:wCont) rounded.
-        hCont := (currentTransformation applyScaleY:hCont) rounded.
-        orgY := currentTransformation translation y negated.
-        orgX := currentTransformation translation x negated
+	wCont := (currentTransformation applyScaleX:wCont) rounded.
+	hCont := (currentTransformation applyScaleY:hCont) rounded.
+	orgY := currentTransformation translation y negated.
+	orgX := currentTransformation translation x negated
     ].
 
     iw := self innerWidth.
@@ -10942,20 +10965,20 @@
     y := newOrigin y.
 
     allowScrollBeyondContents ifFalse:[
-        x + iw > wCont ifTrue:[
-            x := (wCont - iw) asInteger.
-        ].
+	x + iw > wCont ifTrue:[
+	    x := (wCont - iw) asInteger.
+	].
     ].
     x < 0 ifTrue:[
-        x := 0
+	x := 0
     ].
     allowScrollBeyondContents ifFalse:[
-        y + ih > hCont ifTrue:[
-            y := (hCont - ih) asInteger.
-        ].
+	y + ih > hCont ifTrue:[
+	    y := (hCont - ih) asInteger.
+	].
     ].
     y < 0 ifTrue:[
-        y := 0.
+	y := 0.
     ].
 
     dX := x - orgX.
@@ -10966,79 +10989,79 @@
     ].
 
     (wg := self windowGroup) notNil ifTrue:[
-        wg processRealExposeEventsFor:self.
+	wg processRealExposeEventsFor:self.
     ].
 
     self originWillChange.
     (shown and:[doRedraw]) ifTrue:[
-        copyWidth := iw - dX abs.
-        copyHeight := ih - dY abs.
-        ((copyWidth > 0) and:[copyHeight > 0]) ifTrue:[
-            "/ some of the currently displayed pixels
-            "/ remain visible. Copy them
-
-            dX < 0 ifTrue:[
-              fromX := margin.
-              toX := margin - dX.
-              redrawX := margin
-            ] ifFalse:[
-              fromX := margin + dX.
-              toX := margin.
-              redrawX := margin + copyWidth.
-            ].
-            dY < 0 ifTrue:[
-              fromY := margin.
-              toY   := margin - dY.
-              redrawY := margin.
-            ] ifFalse:[
-              fromY := margin + dY.
-              toY   := margin.
-              redrawY := margin + copyHeight.
-            ].
-            self catchExpose.
-            self setViewOrigin:(x @ y).
-            self
-                copyFrom:self
-                x:fromX y:fromY
-                toX:toX   y:toY
-                width:copyWidth
-                height:copyHeight
-                async:true.
-
-            self setInnerClip.
-
-            "first redraw the rectangle above/below the
-             copied area (with full width)."
-
-            copyHeight < ih ifTrue:[
-            self invalidateDeviceRectangle:((margin@redrawY) extent:(iw@(ih - copyHeight))) repairNow:false.
+	copyWidth := iw - dX abs.
+	copyHeight := ih - dY abs.
+	((copyWidth > 0) and:[copyHeight > 0]) ifTrue:[
+	    "/ some of the currently displayed pixels
+	    "/ remain visible. Copy them
+
+	    dX < 0 ifTrue:[
+	      fromX := margin.
+	      toX := margin - dX.
+	      redrawX := margin
+	    ] ifFalse:[
+	      fromX := margin + dX.
+	      toX := margin.
+	      redrawX := margin + copyWidth.
+	    ].
+	    dY < 0 ifTrue:[
+	      fromY := margin.
+	      toY   := margin - dY.
+	      redrawY := margin.
+	    ] ifFalse:[
+	      fromY := margin + dY.
+	      toY   := margin.
+	      redrawY := margin + copyHeight.
+	    ].
+	    self catchExpose.
+	    self setViewOrigin:(x @ y).
+	    self
+		copyFrom:self
+		x:fromX y:fromY
+		toX:toX   y:toY
+		width:copyWidth
+		height:copyHeight
+		async:true.
+
+	    self setInnerClip.
+
+	    "first redraw the rectangle above/below the
+	     copied area (with full width)."
+
+	    copyHeight < ih ifTrue:[
+	    self invalidateDeviceRectangle:((margin@redrawY) extent:(iw@(ih - copyHeight))) repairNow:false.
 "/                self
 "/                    redrawDeviceX:margin y:redrawY
 "/                    width:iw height:(ih - copyHeight).
-            ].
-
-            "second redraw the rectangle left/right of the
-             copied area"
-
-            copyWidth < iw ifTrue:[
-            self invalidateDeviceRectangle:((redrawX@toY) extent:((iw-copyWidth)@copyHeight)) repairNow:false.
+	    ].
+
+	    "second redraw the rectangle left/right of the
+	     copied area"
+
+	    copyWidth < iw ifTrue:[
+	    self invalidateDeviceRectangle:((redrawX@toY) extent:((iw-copyWidth)@copyHeight)) repairNow:false.
 "/                self redrawDeviceX:redrawX y:toY
 "/
 "/                             width:iw - copyWidth
 "/                            height:copyHeight.
-            ].
-            self waitForExpose.
-        ] ifFalse:[
-            "redraw everything"
-
-            self setViewOrigin:(x @ y).
-            self invalidateDeviceRectangle:((margin@margin) extent:(iw@ih)) repairNow:false.
+	    ].
+	    self waitForExpose.
+	] ifFalse:[
+	    "redraw everything"
+
+	    self setViewOrigin:(x @ y).
+	    self invalidateDeviceRectangle:((margin@margin) extent:(iw@ih)) repairNow:false.
 "/            self redrawDeviceX:margin y:margin
 "/                         width:iw
 "/                        height:ih.
-        ].
+	].
     ] ifFalse:[
-        self setViewOrigin:(x @ y).
+	self setViewOrigin:(x @ y).
     ].
 
     self originChanged:(dX negated @ dY negated).
@@ -11237,7 +11260,7 @@
     "Modified: / 9.7.1998 / 01:20:57 / cg"
 !
 
-openModal:aBlock inGroup:aWindowGroup
+openModal:aBlock inGroup:activeWindowGroup
     "create a new windowgroup, but start processing in the current process -
      actually suspending event processing for the main group.
      Stay in this modal loop while aBlock evaluates to true AND the receiver is
@@ -11246,13 +11269,14 @@
      This makes any interaction with the current window impossible -
      however, other views (in other windowgroups) still work."
 
-    |tops mainView previousGroup mainGroup cursorChanged isPopup makeTransient|
+    |tops mainView previousGroup mainGroup cursorChanged 
+     isPopup inSystemProcess makeTransient transientFor|
 
     StandardSystemView cancelAutoRaise.
 
     isPopup := self isPopUpView.
-    aWindowGroup notNil ifTrue:[
-	mainGroup := aWindowGroup mainGroup.
+    activeWindowGroup notNil ifTrue:[
+        mainGroup := activeWindowGroup mainGroup.
 	mainView := mainGroup mainView.
     ].
 
@@ -11260,7 +11284,7 @@
     "/ (so the handler sees me with a wGroup, sensor etc).
     "/ this allows for the handler to enqueue an event,
     "/ or to add event hooks.
-    Processor activeProcessIsSystemProcess ifTrue:[
+    (inSystemProcess := Processor activeProcessIsSystemProcess) ifTrue:[
 	"
 	 put myself into the modal group, let it handle events for
 	 me as well. This is only a half way solution, since the view
@@ -11268,16 +11292,17 @@
 	 where this happens is with modal boxes popped while in a
 	 modal browser. You will forgive me for that inconvenience.
 	"
-	windowGroup := aWindowGroup.
-	aWindowGroup notNil ifTrue:[aWindowGroup addTopView:self].
+        windowGroup := activeWindowGroup.
+        activeWindowGroup notNil ifTrue:[activeWindowGroup addTopView:self].
     ] ifFalse:[
-	previousGroup := WindowGroup activeGroup.
+        previousGroup := activeWindowGroup.
     ].
 
     windowGroup isNil ifTrue:[
 	"/ create a new window group put myself into it
         windowGroup := self windowGroupClass new.
         windowGroup
+            setProcess:Processor activeProcess;
 				addTopView:self;
 				setPreviousGroup:previousGroup.
 
@@ -11285,13 +11310,14 @@
 	    "/
 	    "/ special: this is a modal subview,
 	    "/ prevent the view from reassigning its windowGroup when realized
-	    "/ (subviews normaly place themself into the superviews group)
+            "/ (subviews normally place themself into the superviews group)
 	    "/
 	    windowGroup isForModalSubview:true.
 	].
     ].
 
     makeTransient := true.
+    transientFor := mainView.
     isPopup ifFalse:[
 	"/ the following allows for knowledgable programmers to suppress dialog boxes,
 	"/ or to patch common controls right before opening...
@@ -11310,32 +11336,38 @@
 	"/ the following raises the corresponding mainview, so the dialog shows above
 	"/ any currently covered view. However, be careful if being debugged, or if this dialog
 	"/ is opened by an already open dialog.
-	mainView notNil ifTrue:[
-	    (mainView windowGroup isInModalLoop
-		or:[ mainView windowGroup isDebugged
-		or:[ WindowGroup activeGroup isDebugged
+        (mainView isNil or:[mainView windowGroup isInModalLoop]) ifTrue:[
+            (previousGroup notNil and:[previousGroup isModal]) ifTrue:[
+                transientFor := previousGroup mainView.
+            ].
+        ].
+
+        transientFor notNil ifTrue:[
+            (transientFor windowGroup isInModalLoop
+                or:[ transientFor windowGroup isDebugged
+                or:[ activeWindowGroup isDebugged
 	    ]]) ifFalse:[
 		self tracePoint:#cg message:'activate'.
-		self debuggingCodeFor:#cg is:[ Transcript showCR:mainView; showCR:mainView windowGroup. ].
-		mainView activate; setForegroundWindow.
-	    ] ifTrue:[
-		makeTransient := false.
+                self debuggingCodeFor:#cg is:[ Transcript showCR:transientFor; showCR:transientFor windowGroup. ].
+                transientFor activate; setForegroundWindow.
+"/            ] ifTrue:[
+"/                makeTransient := false.
 	    ]
 	].
     ].
-    makeTransient ifTrue:[
-	mainView notNil ifTrue:[
+    "/ makeTransient ifTrue:[
+        transientFor notNil ifTrue:[
 	    "set the transient property.
 	     This is currently used for X, to tell the Window Manager
 	     That this view should be always on top of the mainView"
 	    self drawableId isNil ifTrue:[self create].
-            device setTransient:self drawableId for:mainView id.
-	]
-    ].
+            device setTransient:self drawableId for:transientFor id.
+        ].
+    "/ ].
 
     self raise.
 
-    Processor activeProcessIsSystemProcess ifTrue:[
+    inSystemProcess ifTrue:[
 	self realize
     ] ifFalse:[
 	"
@@ -11369,16 +11401,16 @@
 	] do:[
 	    [
 		[
-		    windowGroup startupModal:[realized and:aBlock] forGroup:aWindowGroup
+                    windowGroup startupModal:[realized and:aBlock] forGroup:activeWindowGroup
 		] ifCurtailed:[
 		    self hide.
 		]
 	    ] ensure:[
-		aWindowGroup notNil ifTrue:[
-                    aWindowGroup graphicsDevice sync.  "that's a round trip - make sure that all drawing has been processed"
+                activeWindowGroup notNil ifTrue:[
+                    activeWindowGroup graphicsDevice sync.  "that's a round trip - make sure that all drawing has been processed"
 		    "/ ensure that eventListener runs here ...
                     Delay waitForMilliseconds:50.
-		    aWindowGroup processExposeEvents.
+                    activeWindowGroup processExposeEvents.
 
 		    (self isPopUpView or:[ ReturnFocusWhenClosingModalBoxes ]) ifTrue:[
 			"
@@ -11388,8 +11420,8 @@
 			 Only do this, if the previous group is still having the focus.
 			 (i.e. no other view was opened in the meantime)
 			"
-			aWindowGroup graphicsDevice focusView isNil ifTrue:[
-			    tops := aWindowGroup topViews.
+                        activeWindowGroup graphicsDevice focusView isNil ifTrue:[
+                            tops := activeWindowGroup topViews.
 			    (tops notEmptyOrNil) ifTrue:[
 				tops first getKeyboardFocus
 			    ].
@@ -11523,10 +11555,10 @@
     self drawableId isNil ifTrue:[self create].
 
     windowGroup isNil ifTrue:[
-        newGroup := true.
-        windowGroup := self windowGroupClass new.
+	newGroup := true.
+	windowGroup := self windowGroupClass new.
     ] ifFalse:[
-        newGroup := false.
+	newGroup := false.
     ].
 
     windowGroup addTopView:self.
@@ -11535,13 +11567,13 @@
     device nonModalWindowListenersDo:[:listener | listener aboutToOpenWindow:self].
 
     newGroup ifTrue:[
-        (aPoint isNil and:[iconified not]) ifTrue:[
-            windowGroup startupWith:[self realize].
-        ] ifFalse:[
-            windowGroup startupWith:[self realizeKeepingGroup:false at:aPoint iconified:iconified].
-        ].
+	(aPoint isNil and:[iconified not]) ifTrue:[
+	    windowGroup startupWith:[self realize].
+	] ifFalse:[
+	    windowGroup startupWith:[self realizeKeepingGroup:false at:aPoint iconified:iconified].
+	].
     ] ifFalse:[
-        self realizeInGroup.
+	self realizeInGroup.
     ].
 
     "
@@ -11610,45 +11642,45 @@
      another view (which is only available once visible),
      use this to suspend the current process until the receiver is shown.
      Caveat:
-        we poll here for the view to be shown - we need a semaphore
-        which is raised by the view in order to do it right."
+	we poll here for the view to be shown - we need a semaphore
+	which is raised by the view in order to do it right."
 
     |wg n|
 
     n := 0.
     [self shown] whileFalse:[
-        (device notNil and:[device isOpen not]) ifTrue:[^ self].
-
-        "/ this was added to avoid a deadlock, when called from within
-        "/ the event dispatch process (as when doing foo inspect there).
-        n > (10 / 0.05) ifTrue:[
-            'SimpleView [info]: View not visible after 10 seconds - will not wait any longer in waitUntilVisible' infoPrintCR.
-            ^ self
-        ].
-        n := n + 1.
-        Delay waitForMilliseconds:50.
-        (wg := self windowGroup) notNil ifTrue:[
-            wg processExposeEvents.
-        ].
+	(device notNil and:[device isOpen not]) ifTrue:[^ self].
+
+	"/ this was added to avoid a deadlock, when called from within
+	"/ the event dispatch process (as when doing foo inspect there).
+	n > (10 / 0.05) ifTrue:[
+	    'SimpleView [info]: View not visible after 10 seconds - will not wait any longer in waitUntilVisible' infoPrintCR.
+	    ^ self
+	].
+	n := n + 1.
+	Delay waitForMilliseconds:50.
+	(wg := self windowGroup) notNil ifTrue:[
+	    wg processExposeEvents.
+	].
     ].
 
     "does not work (the view is in its opening phase,
      when we attempt to draw a line - this gives an error, since
      its internals are not yet correctly setup):
 
-        |v|
-
-        v := View new open.
-        v displayLineFrom:0@0 to:50@50
+	|v|
+
+	v := View new open.
+	v displayLineFrom:0@0 to:50@50
 
      does work (since we wait until the view has completely finished
      its startup phase):
 
-        |v|
-
-        v := View new open.
-        v waitUntilVisible.
-        v displayLineFrom:0@0 to:50@50
+	|v|
+
+	v := View new open.
+	v waitUntilVisible.
+	v displayLineFrom:0@0 to:50@50
     "
 
     "Modified: / 08-08-2010 / 14:46:34 / cg"
@@ -11818,25 +11850,25 @@
     be wrapped by other programs.
 
     i.e. its typical use is like:
-        Dialog boxClosedNotificationSignal handle:[:ex |
-            Transcript showCR:'box closed'
-        ] do:[
-            Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
-                Transcript showCR:'box about to open'
-            ] do:[
-                Dialog information:'This is a standard information box.'.
-            ].
-        ].
-
-        Dialog boxClosedNotificationSignal handle:[:ex |
-            Transcript showCR:'box closed'
-        ] do:[
-            Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
-                Transcript showCR:'box about to open'
-            ] do:[
-                Dialog confirm:'Yes or No.'.
-            ].
-        ].
+	Dialog boxClosedNotificationSignal handle:[:ex |
+	    Transcript showCR:'box closed'
+	] do:[
+	    Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
+		Transcript showCR:'box about to open'
+	    ] do:[
+		Dialog information:'This is a standard information box.'.
+	    ].
+	].
+
+	Dialog boxClosedNotificationSignal handle:[:ex |
+	    Transcript showCR:'box closed'
+	] do:[
+	    Dialog aboutToOpenBoxNotificationSignal handle:[:ex |
+		Transcript showCR:'box about to open'
+	    ] do:[
+		Dialog confirm:'Yes or No.'.
+	    ].
+	].
 "
 ! !
 
--- a/StandardSystemView.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/StandardSystemView.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -615,49 +613,49 @@
 
 sizeFixed:aBoolean
     "this prevents the view from resizing itself when realized.
-     For normal topViews, this is void, since they dont do this anyway.
+     For normal topViews, this is void, since they don't do this anyway.
 
      However, modalBoxes (especially: DialogBoxes) typically resize themselfes
      to the preferredExtent of their components. In some cases, this behavior is
      not desired and it should be turned off by setting sizeFixed to true.
 
      To avoid confusion:
-	This does NOT prevent the window manager from resizing the view,
-	instead it tells the view to NOT resize ITSELF."
+        This does NOT prevent the window manager from resizing the view,
+        instead it tells the view to NOT resize ITSELF."
 
     sizeFixed := aBoolean.
 
     "example: dialog which resizes itself on #open:
-	      (thereby ignoring the 200@200 extent)
+              (thereby ignoring the 200@200 extent)
 
-	|dialog|
+        |dialog|
 
-	dialog := Dialog new.
-	dialog addInputFieldOn:'' asValue.
-	dialog addOkButton.
-	dialog extent:200@200.
-	dialog open.
+        dialog := Dialog new.
+        dialog addInputFieldOn:'' asValue.
+        dialog addOkButton.
+        dialog extent:200@200.
+        dialog open.
 
 
     using sizeFixed:
 
-	|dialog|
+        |dialog|
 
-	dialog := Dialog new.
-	dialog addInputFieldOn:'' asValue.
-	dialog addOkButton.
-	dialog extent:200@200; sizeFixed:true.
-	dialog open.
+        dialog := Dialog new.
+        dialog addInputFieldOn:'' asValue.
+        dialog addOkButton.
+        dialog extent:200@200; sizeFixed:true.
+        dialog open.
 
 
     using openWithExtent (also sets sizeFixed):
 
-	|dialog|
+        |dialog|
 
-	dialog := Dialog new.
-	dialog addInputFieldOn:'' asValue.
-	dialog addOkButton.
-	dialog openWithExtent:200@200.
+        dialog := Dialog new.
+        dialog addInputFieldOn:'' asValue.
+        dialog addOkButton.
+        dialog openWithExtent:200@200.
     "
 ! !
 
--- a/SynchronousWindowSensor.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/SynchronousWindowSensor.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1995 by Claus Gittinger
 	      All Rights Reserved
@@ -55,7 +53,7 @@
     to prevent the event handling code from suspending any process
     (you cannot suspend the scheduler; you should not suspend the event dispatcher).
 
-    This is pretty tricky and magic - and you dont have to understand this.
+    This is pretty tricky and magic - and you don't have to understand this.
     (consider this system internal code)
 
     [author:]
--- a/TopView.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/TopView.st	Fri Nov 18 21:26:33 2016 +0000
@@ -723,6 +723,13 @@
      mouse-enter/leave time."
 
     ^ false
+!
+
+flyByHelpSpec
+    ^ nil
+
+    "FlyByHelp >> #helpTextFromView:at: calls this method:
+        aView topView flyByHelpSpec notNil"
 ! !
 
 !TopView methodsFor:'help stubs'!
--- a/View.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/View.st	Fri Nov 18 21:26:33 2016 +0000
@@ -336,7 +336,7 @@
     (model isNil 
     or:[model isValueModel
     or:[model isBlock]]) ifTrue:[
-        "/ a simple holder-model. dont send menuMessages to it
+        "/ a simple holder-model. don't send menuMessages to it
         ^ self application ? self
     ].
     ^ model
@@ -586,8 +586,6 @@
 sendChangeMessage:aSelector with:arg
     "tell the model about a change"
 
-    |n selector|
-
     "/
     "/ MVC way of doing it:
     "/ if the model is a block, evaluate it, optionally
@@ -598,43 +596,10 @@
     "/ as defined by the selector).
     "/
     (model notNil and:[aSelector notNil]) ifTrue:[
-        n := aSelector numArgs.
         model isBlock ifTrue:[
-            n := model numArgs.
-            n == 0 ifTrue:[
-                selector := #value
-            ] ifFalse:[
-                n == 1 ifTrue:[
-                    selector := #value:
-                ] ifFalse:[
-                    selector := #value:value:
-                ]
-            ]
-        ] ifFalse:[
-            selector := aSelector
-        ].
-        n == 0 ifTrue:[
-            model perform:selector 
+            model valueWithOptionalArgument:aSelector and:arg and:self.
         ] ifFalse:[
-            selector == #value: ifTrue:[
-                "/ must take care, if model is == to the selection-collection
-                "/ in this case, we must force a change on the model
-                "/ (valueHolder would not send a change in the == case)
-                "/ Q: is this a good idea, or should it be done
-                "/    at the invoking side
-"/                model isValueModel ifTrue:[
-"/                    model value == arg ifTrue:[
-"/                        model setValue:nil.
-"/                    ]
-"/                ].
-                model value:arg
-            ] ifFalse:[
-                n == 1 ifTrue:[
-                    model perform:selector with:arg
-                ] ifFalse:[
-                    model perform:selector with:arg with:self 
-                ]
-            ]
+            model perform:aSelector withOptionalArgument:arg and:self.
         ]
     ]
 !
--- a/WinWorkstation.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/WinWorkstation.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1102,11 +1102,6 @@
 
 extern HANDLE __getHInstance();
 
-#ifdef xxWIN32THREADS
-extern void __suspendAktThread();
-extern void __resumeAktThread();
-#endif
-
 static void __debugEvent__() {}
 
 #ifdef DEBUGMASK
@@ -1134,15 +1129,8 @@
 static int
 st2RGB(int color, struct gcData *gcData)
 {
-	int ir,ig,ib;
-
-	if (gcData) {
-	    if (gcData->bitmapColorBitCount == 1) {
-	      if (color)
-		  return WhitePixel;
-	      else
-		  return BlackPixel;
-	    }
+	if (gcData && gcData->bitmapColorBitCount == 1) {
+	    return (color ? WhitePixel : BlackPixel);
 	}
 #ifdef ALWAYSTRUECOLOR
 	return (color & 0xffffff);
@@ -1151,9 +1139,9 @@
 	    return 0;
 	} else {
 	    if ((__depth == 16) || (__depth == 15)) {
-		ib = (color & 0x1f) << 3;
-		ig = ((color >> 5) & 0x3f) << 2;
-		ir = ((color >> 11) & 0x1f) << 3;
+		int ib = (color & 0x1f) << 3;
+		int ig = ((color >> 5) & 0x3f) << 2;
+		int ir = ((color >> 11) & 0x1f) << 3;
 		ir |= 7;
 		ig |= 3;
 		ib |= 7;
@@ -1165,8 +1153,7 @@
 }
 
 static int
-RGB2st(r, g, b)
-    int r, g, b;
+RGB2st(int r, int g, int b)
 {
 	int ir,ig,ib,id;
 
@@ -1203,8 +1190,7 @@
  * return a windows top-window
  */
 static HWND
-GetTopParent(hWnd)
-    HWND hwnd;
+GetTopParent(HWND hwnd)
 {
 	HWND lastParent = hWnd;
 	HWND nextParent;
@@ -1247,11 +1233,8 @@
 static int
 _DeleteBrush(HBRUSH br, int lineNr)
 {
-    int r;
-
-    if ((br != __whiteBrush)
-     && (br != __blackBrush)) {
-	r = DeleteObject(br);
+    if ((br != __whiteBrush) && (br != __blackBrush)) {
+	int r = DeleteObject(br);
 
 	if (r == 0)
 	    console_fprintf(stderr, "WinWorkstation [warning]: ERROR in DeleteBrush %x [%d]\n", br, lineNr);
@@ -1263,11 +1246,8 @@
 static int
 _DeletePen(HPEN p, int lineNr)
 {
-    int r;
-
-    if ((p != __whitePen)
-     && (p != __blackPen)) {
-	r = DeleteObject(p);
+    if ((p != __whitePen) && (p != __blackPen)) {
+	int r = DeleteObject(p);
 
 	if (r == 0)
 	    console_fprintf(stderr, "WinWorkstation [warning]: ERROR in DeletePen %x [%d]\n", p, lineNr);
@@ -1283,8 +1263,7 @@
 {
     int i, r;
 
-    if ((p == __whitePen)
-     || (p == __blackPen)) {
+    if ((p == __whitePen) || (p == __blackPen)) {
 	return 1; /* not deleted, but OK */
     }
     for (i=0; i<NUM_PEN_CACHED;i++) {
@@ -1315,8 +1294,7 @@
 	    return 1; /* not deleted, but OK */
 	}
     }
-    if ((br == __whiteBrush)
-     || (br == __blackBrush)) {
+    if ((br == __whiteBrush) || (br == __blackBrush)) {
 	return 1; /* not deleted, but OK */
     }
     r = DeleteObject(br);
@@ -1649,9 +1627,8 @@
 static void
 GcDataReleaseBrush(HDC hDC, struct gcData *gcData)
 {
-    HBRUSH hBrush;
-
-    hBrush = gcData->hBrush;
+    HBRUSH hBrush = gcData->hBrush;
+
     if (gcData->save_hBrush) {
 	SelectObject(hDC, gcData->save_hBrush);
 	gcData->save_hBrush = NULL;
@@ -1884,7 +1861,7 @@
 }
 
 static int
-unlockEvents() {
+unlockEvents(void) {
 #ifdef LOCK_DEBUG
     lockCountEvents--;
     if (lockCountEvents != 0) {
@@ -1903,7 +1880,7 @@
 
 
 static int
-initEventqueue() {
+initEventqueue(void) {
     struct queuedEvent *bulk;
     int i;
 
@@ -2235,7 +2212,6 @@
  * if a region is passed in, it is not destroyed.
  */
 
-
 static int
 __generateExposes(HWND hWnd, HRGN hRgnInOrNull, int msgType, int doClear)
 {
@@ -2382,7 +2358,7 @@
 
 
 static int
-getModifiers()
+getModifiers(void)
 {
     int modifiers = 0;
 
@@ -4313,16 +4289,13 @@
 	case WM_COPYDATA:
 	    DPRINTFIF(__debug_WM_COPYDATA__ , ("WM_COPYDATA\n"));
 	    {
-		PCOPYDATASTRUCT pCDs;
-		int dwData;
-		void *pData;
+		PCOPYDATASTRUCT pCDs = (PCOPYDATASTRUCT) lParam;
+		int dwData = pCDs->dwData;
+		int nBytes = pCDs->cbData;
+		void *pData = pCDs->lpData;
 		void *pCopiedData;
-		int nBytes;
-
-		pCDs = (PCOPYDATASTRUCT) lParam;
-		dwData = pCDs->dwData;
-		nBytes = pCDs->cbData;
-		pData = (void *)pCDs->lpData;
+
+		DPRINTFIF(__debug_WM_COPYDATA__ , ("WM_COPYDATA %d %lx\n", nBytes, pData));
 
 		/*
 		 * because pData is only valid here, copy it out to a malloc'd
@@ -4335,7 +4308,7 @@
 		    pCopiedData = NULL;
 		}
 		//     (flag, hWnd, message, wParam, arg1, arg2, arg3, arg4, evTime)
-		enqEvent(0, hWnd, WM_COPYDATA, wParam, (INT)pCopiedData, nBytes, 0, 0, EV_NOTIME);
+		enqEvent(0, hWnd, WM_COPYDATA, wParam, (INT)pCopiedData, nBytes, dwData, 0, EV_NOTIME);
 	    }
 	    *pDefault = 0;
 	    break;
@@ -4562,8 +4535,6 @@
     return 0;
 }
 
-LONG APIENTRY
-MainWndProc(HWND hWnd,UINT message,UINT wParam,LONG lParam);
 
 static void _USERENTRY
 dispatchThread(void *arg)
@@ -4968,26 +4939,26 @@
 	return TRUE;
 }
 
-#define xxUSE_EnumFontFamiliesEx
+#ifdef USE_EnumFontFamiliesEx
+# define LOGFONTTYPE  ENUMLOGFONTEX
+#else
+# define LOGFONTTYPE  LOGFONT
+#endif
 
 static int CALLBACK
-EnumFPTypeFaceProc( lplf, lptm, dwType, lpData )
-#ifdef USE_EnumFontFamiliesEx
-	ENUMLOGFONTEX   *lplf;
-#else
-	LOGFONT         *lplf;
-#endif
-	TEXTMETRIC      *lptm;
-	DWORD           dwType;
-	void            *lpData;
-{
+EnumFPTypeFaceProc(
+    const LOGFONTTYPE *lplf,   /* ptr to of logical-font data */
+    const TEXTMETRIC  *lptm,   /* ptr to physical font data */
+    DWORD dwType,              /* font type */
+    LPARAM lpData              /* application supplied data */
+) {
 	OBJ t;
 	volatile OBJ *refToList;
 	OBJ  typeFaceList;
 	char *faceNameString;
 
 	if (lplf) {
-	    refToList = (OBJ*) lpData;
+	    refToList = (OBJ *) lpData;
 	    __PROTECT__(*refToList);
 
 #ifdef USE_EnumFontFamiliesEx
@@ -5238,17 +5209,14 @@
 	return newArray;
 }
 
+
 static int CALLBACK
-EnumFontsProc( lplf, lptm, dwType, lpData )
-#ifdef USE_EnumFontFamiliesEx
-	ENUMLOGFONTEX   *lplf;
-#else
-	LOGFONT         *lplf;     /* ptr to of logical-font data */
-#endif
-	TEXTMETRIC      *lptm;     /* ptr to physical font data */
-	DWORD           dwType;    /* font type */
-	void            *lpData;   /* application supplied data */
-{
+EnumFontsProc(
+    const LOGFONTTYPE *lplf,   // ptr to of logical-font data
+    const TEXTMETRIC *lptm,    // ptr to physical font data
+    DWORD dwType,              // font type
+    LPARAM lpData              // application supplied data
+) {
 	volatile OBJ *refToList;
 	OBJ list;
 	OBJ infoArray;
@@ -5257,7 +5225,7 @@
 	DPRINTF(("EnumFontsProc\n"));
 
 	if ( lplf ) {
-	    refToList = (OBJ*) lpData;
+	    refToList = (OBJ *) lpData;
 
 	    __PROTECT__(*refToList);
 #ifdef USE_EnumFontFamiliesEx
@@ -5288,21 +5256,17 @@
 };
 
 static int CALLBACK
-EnumDisplayMonitorsProc( hMonitor, hdcMonitor, lprcMonitor, lpData )
-    HMONITOR hMonitor;
-    HDC hdcMonitor;
-    LPRECT lprcMonitor;
-    struct EnumDisplayMonitorsProcData *lpData;
+EnumDisplayMonitorsProc(HMONITOR hMonitor, HDC hdcMonitor, LPRECT lprcMonitor, LPARAM lpData)
 {
+    struct EnumDisplayMonitorsProcData *procData = (struct EnumDisplayMonitorsProcData *)lpData;
     OBJ mHandle;
 
-    __PROTECT__(lpData->hArray);
+    __PROTECT__(procData->hArray);
     mHandle = __MKEXTERNALADDRESS(hMonitor);
-    __UNPROTECT__(lpData->hArray);
-
-    __ArrayInstPtr(lpData->hArray)->a_element[lpData->index] = mHandle;
-    __STORE(lpData->hArray, mHandle);
-    lpData->index++;
+    __UNPROTECT__(procData->hArray);
+
+    __arrayVal(procData->hArray)[procData->index++] = mHandle;
+    __STORE(procData->hArray, mHandle);
     return (1);
 }
 
@@ -5342,14 +5306,12 @@
     self initializeStandardColorNames.
 
     NativeWidgets := NativeDialogs := NativeFileDialogs := false.
-
     BeepDuration := 200.        "milliseconds"
-
     ButtonTranslation := #(1 2 2).
 
     "/ SysColorChanges are reported *very* often when exceed is running,
     "/ but are also needed to update my view colors when the settings change.
-    "/ I dont know what exceed is doing there ...
+    "/ I don't know what exceed is doing there ...
     "/ IgnoreSysColorChanges := true.
     IgnoreSysColorChanges := false.
     SystemColorValues := IdentityDictionary new.
@@ -5357,18 +5319,20 @@
     "/ translation table from ST/X windowType symbol (system-independent)
     "/ to Windows windowClass (windows-specific).
 
-    NativeWidgetClassTable := IdentityDictionary new.
-    NativeWidgetClassTable at:#ScrollBar                put:'SCROLLBAR'.
-    NativeWidgetClassTable at:#HorizontalScrollBar      put:'SCROLLBAR'.
-    NativeWidgetClassTable at:#VerticalScrollBar        put:'SCROLLBAR'.
-    NativeWidgetClassTable at:#CheckBox                 put:'BUTTON'.
-    NativeWidgetClassTable at:#RadioButton              put:'BUTTON'.
-    NativeWidgetClassTable at:#Button                   put:'BUTTON'.
-    NativeWidgetClassTable at:#DefaultButton            put:'BUTTON'.
-    NativeWidgetClassTable at:#OwnerDrawButton          put:'BUTTON'.
-    NativeWidgetClassTable at:#ComboBox                 put:'COMBOBOX'.
-    NativeWidgetClassTable at:#EditField                put:'EDIT'.
-    NativeWidgetClassTable at:#ListBox                  put:'LISTBOX'.
+    NativeWidgetClassTable := IdentityDictionary
+	withKeysAndValues:#(
+		ScrollBar                 SCROLLBAR
+		HorizontalScrollBar       SCROLLBAR
+		VerticalScrollBar         SCROLLBAR
+		CheckBox                  BUTTON
+		RadioButton               BUTTON
+		Button                    BUTTON
+		DefaultButton             BUTTON
+		OwnerDrawButton           BUTTON
+		ComboBox                  COMBOBOX
+		EditField                 EDIT
+		ListBox                   LISTBOX
+	).
 
     "Modified: / 24-08-2010 / 16:42:23 / sr"
 !
@@ -5378,820 +5342,818 @@
 
     "setup standard color names (X-color names)"
 
-    StandardColorValues := Dictionary new.
-    #(
-	(240 248 255)   'aliceblue'
-	(250 235 215)   'antiquewhite'
-	(255 239 219)   'AntiqueWhite1'
-	(238 223 204)   'AntiqueWhite2'
-	(205 192 176)   'AntiqueWhite3'
-	(139 131 120)   'AntiqueWhite4'
-	(127 255 212)   'aquamarine'
-	(127 255 212)   'aquamarine1'
-	(118 238 198)   'aquamarine2'
-	(102 205 170)   'aquamarine3'
-	( 69 139 116)   'aquamarine4'
-	(240 255 255)   'azure'
-	(240 255 255)   'azure1'
-	(224 238 238)   'azure2'
-	(193 205 205)   'azure3'
-	(131 139 139)   'azure4'
-	(245 245 220)   'beige'
-	(255 228 196)   'bisque'
-	(255 228 196)   'bisque1'
-	(238 213 183)   'bisque2'
-	(205 183 158)   'bisque3'
-	(139 125 107)   'bisque4'
-	(  0   0   0)   'black'
-	(255 235 205)   'blanchedalmond'
-	(  0   0 255)   'blue'
-	(138  43 226)   'blueviolet'
-	(  0   0 255)   'blue1'
-	(  0   0 238)   'blue2'
-	(  0   0 205)   'blue3'
-	(  0   0 139)   'blue4'
-	(165  42  42)   'brown'
-	(255  64  64)   'brown1'
-	(238  59  59)   'brown2'
-	(205  51  51)   'brown3'
-	(139  35  35)   'brown4'
-	(222 184 135)   'burlywood'
-	(255 211 155)   'burlywood1'
-	(238 197 145)   'burlywood2'
-	(205 170 125)   'burlywood3'
-	(139 115  85)   'burlywood4'
-	( 95 158 160)   'cadetblue'
-	(152 245 255)   'CadetBlue1'
-	(142 229 238)   'CadetBlue2'
-	(122 197 205)   'CadetBlue3'
-	( 83 134 139)   'CadetBlue4'
-	(127 255   0)   'chartreuse'
-	(127 255   0)   'chartreuse1'
-	(118 238   0)   'chartreuse2'
-	(102 205   0)   'chartreuse3'
-	( 69 139   0)   'chartreuse4'
-	(210 105  30)   'chocolate'
-	(255 127  36)   'chocolate1'
-	(238 118  33)   'chocolate2'
-	(205 102  29)   'chocolate3'
-	(139  69  19)   'chocolate4'
-	(255 127  80)   'coral'
-	(255 114  86)   'coral1'
-	(238 106  80)   'coral2'
-	(205  91  69)   'coral3'
-	(139  62  47)   'coral4'
-	(100 149 237)   'cornflowerblue'
-	(255 248 220)   'cornsilk'
-	(255 248 220)   'cornsilk1'
-	(238 232 205)   'cornsilk2'
-	(205 200 177)   'cornsilk3'
-	(139 136 120)   'cornsilk4'
-	(  0 255 255)   'cyan'
-	(  0 255 255)   'cyan1'
-	(  0 238 238)   'cyan2'
-	(  0 205 205)   'cyan3'
-	(  0 139 139)   'cyan4'
-	(  0   0 139)   'darkblue'
-	(  0 139 139)   'darkcyan'
-	(184 134  11)   'darkgoldenrod'
-	(169 169 169)   'darkgray'
-	(  0 100   0)   'darkgreen'
-	(169 169 169)   'darkgrey'
-	(189 183 107)   'darkkhaki'
-	(139   0 139)   'darkmagenta'
-	( 85 107  47)   'darkolivegreen'
-	(255 140   0)   'darkorange'
-	(153  50 204)   'darkorchid'
-	(139   0   0)   'darkred'
-	(233 150 122)   'darksalmon'
-	(143 188 143)   'darkseagreen'
-	( 72  61 139)   'darkslateblue'
-	( 47  79  79)   'darkslategray'
-	( 47  79  79)   'darkslategrey'
-	(  0 206 209)   'darkturquoise'
-	(148   0 211)   'darkviolet'
-	(255 185  15)   'DarkGoldenrod1'
-	(238 173  14)   'DarkGoldenrod2'
-	(205 149  12)   'DarkGoldenrod3'
-	(139 101   8)   'DarkGoldenrod4'
-	(202 255 112)   'DarkOliveGreen1'
-	(188 238 104)   'DarkOliveGreen2'
-	(162 205  90)   'DarkOliveGreen3'
-	(110 139  61)   'DarkOliveGreen4'
-	(255 127   0)   'DarkOrange1'
-	(238 118   0)   'DarkOrange2'
-	(205 102   0)   'DarkOrange3'
-	(139  69   0)   'DarkOrange4'
-	(191  62 255)   'DarkOrchid1'
-	(178  58 238)   'DarkOrchid2'
-	(154  50 205)   'DarkOrchid3'
-	(104  34 139)   'DarkOrchid4'
-	(193 255 193)   'DarkSeaGreen1'
-	(180 238 180)   'DarkSeaGreen2'
-	(155 205 155)   'DarkSeaGreen3'
-	(105 139 105)   'DarkSeaGreen4'
-	(151 255 255)   'DarkSlateGray1'
-	(141 238 238)   'DarkSlateGray2'
-	(121 205 205)   'DarkSlateGray3'
-	( 82 139 139)   'DarkSlateGray4'
-	(255  20 147)   'deeppink'
-	(  0 191 255)   'deepskyblue'
-	(255  20 147)   'DeepPink'
-	(255  20 147)   'DeepPink1'
-	(238  18 137)   'DeepPink2'
-	(205  16 118)   'DeepPink3'
-	(139  10  80)   'DeepPink4'
-	(  0 191 255)   'DeepSkyBlue1'
-	(  0 178 238)   'DeepSkyBlue2'
-	(  0 154 205)   'DeepSkyBlue3'
-	(  0 104 139)   'DeepSkyBlue4'
-	(105 105 105)   'dimgray'
-	(105 105 105)   'dimgrey'
-	( 30 144 255)   'dodgerblue'
-	( 30 144 255)   'DodgerBlue1'
-	( 28 134 238)   'DodgerBlue2'
-	( 24 116 205)   'DodgerBlue3'
-	( 16  78 139)   'DodgerBlue4'
-	(178  34  34)   'firebrick'
-	(255  48  48)   'firebrick1'
-	(238  44  44)   'firebrick2'
-	(205  38  38)   'firebrick3'
-	(139  26  26)   'firebrick4'
-	(255 250 240)   'floralwhite'
-	( 34 139  34)   'forestgreen'
-	(220 220 220)   'gainsboro'
-	(248 248 255)   'ghostwhite'
-	(255 215   0)   'gold'
-	(255 215   0)   'gold1'
-	(238 201   0)   'gold2'
-	(205 173   0)   'gold3'
-	(139 117   0)   'gold4'
-	(218 165  32)   'goldenrod'
-	(255 193  37)   'goldenrod1'
-	(238 180  34)   'goldenrod2'
-	(205 155  29)   'goldenrod3'
-	(139 105  20)   'goldenrod4'
-	(192 192 192)   'grey'
-	(  0   0   0)   'grey0'
-	(  3   3   3)   'grey1'
-	( 26  26  26)   'grey10'
-	(255 255 255)   'grey100'
-	( 28  28  28)   'grey11'
-	( 31  31  31)   'grey12'
-	( 33  33  33)   'grey13'
-	( 36  36  36)   'grey14'
-	( 38  38  38)   'grey15'
-	( 41  41  41)   'grey16'
-	( 43  43  43)   'grey17'
-	( 46  46  46)   'grey18'
-	( 48  48  48)   'grey19'
-	(  5   5   5)   'grey2'
-	( 51  51  51)   'grey20'
-	( 54  54  54)   'grey21'
-	( 56  56  56)   'grey22'
-	( 59  59  59)   'grey23'
-	( 61  61  61)   'grey24'
-	( 64  64  64)   'grey25'
-	( 66  66  66)   'grey26'
-	( 69  69  69)   'grey27'
-	( 71  71  71)   'grey28'
-	( 74  74  74)   'grey29'
-	(  8   8   8)   'grey3'
-	( 77  77  77)   'grey30'
-	( 79  79  79)   'grey31'
-	( 82  82  82)   'grey32'
-	( 84  84  84)   'grey33'
-	( 87  87  87)   'grey34'
-	( 89  89  89)   'grey35'
-	( 92  92  92)   'grey36'
-	( 94  94  94)   'grey37'
-	( 97  97  97)   'grey38'
-	( 99  99  99)   'grey39'
-	( 10  10  10)   'grey4'
-	(102 102 102)   'grey40'
-	(105 105 105)   'grey41'
-	(107 107 107)   'grey42'
-	(110 110 110)   'grey43'
-	(112 112 112)   'grey44'
-	(115 115 115)   'grey45'
-	(117 117 117)   'grey46'
-	(120 120 120)   'grey47'
-	(122 122 122)   'grey48'
-	(125 125 125)   'grey49'
-	( 13  13  13)   'grey5'
-	(127 127 127)   'grey50'
-	(130 130 130)   'grey51'
-	(133 133 133)   'grey52'
-	(135 135 135)   'grey53'
-	(138 138 138)   'grey54'
-	(140 140 140)   'grey55'
-	(143 143 143)   'grey56'
-	(145 145 145)   'grey57'
-	(148 148 148)   'grey58'
-	(150 150 150)   'grey59'
-	( 15  15  15)   'grey6'
-	(153 153 153)   'grey60'
-	(156 156 156)   'grey61'
-	(158 158 158)   'grey62'
-	(161 161 161)   'grey63'
-	(163 163 163)   'grey64'
-	(166 166 166)   'grey65'
-	(168 168 168)   'grey66'
-	(171 171 171)   'grey67'
-	(173 173 173)   'grey68'
-	(176 176 176)   'grey69'
-	( 18  18  18)   'grey7'
-	(179 179 179)   'grey70'
-	(181 181 181)   'grey71'
-	(184 184 184)   'grey72'
-	(186 186 186)   'grey73'
-	(189 189 189)   'grey74'
-	(191 191 191)   'grey75'
-	(194 194 194)   'grey76'
-	(196 196 196)   'grey77'
-	(199 199 199)   'grey78'
-	(201 201 201)   'grey79'
-	( 20  20  20)   'grey8'
-	(204 204 204)   'grey80'
-	(207 207 207)   'grey81'
-	(209 209 209)   'grey82'
-	(212 212 212)   'grey83'
-	(214 214 214)   'grey84'
-	(217 217 217)   'grey85'
-	(219 219 219)   'grey86'
-	(222 222 222)   'grey87'
-	(224 224 224)   'grey88'
-	(227 227 227)   'grey89'
-	( 23  23  23)   'grey9'
-	(229 229 229)   'grey90'
-	(232 232 232)   'grey91'
-	(235 235 235)   'grey92'
-	(237 237 237)   'grey93'
-	(240 240 240)   'grey94'
-	(242 242 242)   'grey95'
-	(245 245 245)   'grey96'
-	(247 247 247)   'grey97'
-	(250 250 250)   'grey98'
-	(252 252 252)   'grey99'
-
-	(192 192 192)   'gray'
-	(  0   0   0)   'gray0'
-	(  3   3   3)   'gray1'
-	( 26  26  26)   'gray10'
-	(255 255 255)   'gray100'
-	( 28  28  28)   'gray11'
-	( 31  31  31)   'gray12'
-	( 33  33  33)   'gray13'
-	( 36  36  36)   'gray14'
-	( 38  38  38)   'gray15'
-	( 41  41  41)   'gray16'
-	( 43  43  43)   'gray17'
-	( 46  46  46)   'gray18'
-	( 48  48  48)   'gray19'
-	(  5   5   5)   'gray2'
-	( 51  51  51)   'gray20'
-	( 54  54  54)   'gray21'
-	( 56  56  56)   'gray22'
-	( 59  59  59)   'gray23'
-	( 61  61  61)   'gray24'
-	( 64  64  64)   'gray25'
-	( 66  66  66)   'gray26'
-	( 69  69  69)   'gray27'
-	( 71  71  71)   'gray28'
-	( 74  74  74)   'gray29'
-	(  8   8   8)   'gray3'
-	( 77  77  77)   'gray30'
-	( 79  79  79)   'gray31'
-	( 82  82  82)   'gray32'
-	( 84  84  84)   'gray33'
-	( 87  87  87)   'gray34'
-	( 89  89  89)   'gray35'
-	( 92  92  92)   'gray36'
-	( 94  94  94)   'gray37'
-	( 97  97  97)   'gray38'
-	( 99  99  99)   'gray39'
-	( 10  10  10)   'gray4'
-	(102 102 102)   'gray40'
-	(105 105 105)   'gray41'
-	(107 107 107)   'gray42'
-	(110 110 110)   'gray43'
-	(112 112 112)   'gray44'
-	(115 115 115)   'gray45'
-	(117 117 117)   'gray46'
-	(120 120 120)   'gray47'
-	(122 122 122)   'gray48'
-	(125 125 125)   'gray49'
-	( 13  13  13)   'gray5'
-	(127 127 127)   'gray50'
-	(130 130 130)   'gray51'
-	(133 133 133)   'gray52'
-	(135 135 135)   'gray53'
-	(138 138 138)   'gray54'
-	(140 140 140)   'gray55'
-	(143 143 143)   'gray56'
-	(145 145 145)   'gray57'
-	(148 148 148)   'gray58'
-	(150 150 150)   'gray59'
-	( 15  15  15)   'gray6'
-	(153 153 153)   'gray60'
-	(156 156 156)   'gray61'
-	(158 158 158)   'gray62'
-	(161 161 161)   'gray63'
-	(163 163 163)   'gray64'
-	(166 166 166)   'gray65'
-	(168 168 168)   'gray66'
-	(171 171 171)   'gray67'
-	(173 173 173)   'gray68'
-	(176 176 176)   'gray69'
-	( 18  18  18)   'gray7'
-	(179 179 179)   'gray70'
-	(181 181 181)   'gray71'
-	(184 184 184)   'gray72'
-	(186 186 186)   'gray73'
-	(189 189 189)   'gray74'
-	(191 191 191)   'gray75'
-	(194 194 194)   'gray76'
-	(196 196 196)   'gray77'
-	(199 199 199)   'gray78'
-	(201 201 201)   'gray79'
-	( 20  20  20)   'gray8'
-	(204 204 204)   'gray80'
-	(207 207 207)   'gray81'
-	(209 209 209)   'gray82'
-	(212 212 212)   'gray83'
-	(214 214 214)   'gray84'
-	(217 217 217)   'gray85'
-	(219 219 219)   'gray86'
-	(222 222 222)   'gray87'
-	(224 224 224)   'gray88'
-	(227 227 227)   'gray89'
-	( 23  23  23)   'gray9'
-	(229 229 229)   'gray90'
-	(232 232 232)   'gray91'
-	(235 235 235)   'gray92'
-	(237 237 237)   'gray93'
-	(240 240 240)   'gray94'
-	(242 242 242)   'gray95'
-	(245 245 245)   'gray96'
-	(247 247 247)   'gray97'
-	(250 250 250)   'gray98'
-	(252 252 252)   'gray99'
-	(  0 255   0)   'green'
-	(173 255  47)   'greenyellow'
-	(  0 255   0)   'green1'
-	(  0 238   0)   'green2'
-	(  0 205   0)   'green3'
-	(  0 139   0)   'green4'
-	(240 255 240)   'honeydew'
-	(240 255 240)   'honeydew1'
-	(224 238 224)   'honeydew2'
-	(193 205 193)   'honeydew3'
-	(131 139 131)   'honeydew4'
-	(255 105 180)   'hotpink'
-	(255 110 180)   'HotPink1'
-	(238 106 167)   'HotPink2'
-	(205  96 144)   'HotPink3'
-	(139  58  98)   'HotPink4'
-	(205  92  92)   'indianred'
-	(255 106 106)   'IndianRed1'
-	(238  99  99)   'IndianRed2'
-	(205  85  85)   'IndianRed3'
-	(139  58  58)   'IndianRed4'
-	(255 255 240)   'ivory'
-	(255 255 240)   'ivory1'
-	(238 238 224)   'ivory2'
-	(205 205 193)   'ivory3'
-	(139 139 131)   'ivory4'
-	(240 230 140)   'khaki'
-	(255 246 143)   'khaki1'
-	(238 230 133)   'khaki2'
-	(205 198 115)   'khaki3'
-	(139 134  78)   'khaki4'
-	(230 230 250)   'lavender'
-	(255 240 245)   'lavenderblush'
-	(255 240 245)   'LavenderBlush1'
-	(238 224 229)   'LavenderBlush2'
-	(205 193 197)   'LavenderBlush3'
-	(139 131 134)   'LavenderBlush4'
-	(124 252   0)   'lawngreen'
-	(255 250 205)   'lemonchiffon'
-	(255 250 205)   'LemonChiffon1'
-	(238 233 191)   'LemonChiffon2'
-	(205 201 165)   'LemonChiffon3'
-	(139 137 112)   'LemonChiffon4'
-	(173 216 230)   'lightblue'
-	(240 128 128)   'lightcoral'
-	(224 255 255)   'lightcyan'
-	(238 221 130)   'lightgoldenrod'
-	(250 250 210)   'lightgoldenrodyellow'
-	(211 211 211)   'lightgray'
-	(144 238 144)   'lightgreen'
-	(211 211 211)   'lightgrey'
-	(255 182 193)   'lightpink'
-	(255 160 122)   'lightsalmon'
-	( 32 178 170)   'lightseagreen'
-	(135 206 250)   'lightskyblue'
-	(132 112 255)   'lightslateblue'
-	(119 136 153)   'lightslategray'
-	(119 136 153)   'lightslategrey'
-	(176 196 222)   'lightsteelblue'
-	(255 255 224)   'lightyellow'
-	(191 239 255)   'LightBlue1'
-	(178 223 238)   'LightBlue2'
-	(154 192 205)   'LightBlue3'
-	(104 131 139)   'LightBlue4'
-	(224 255 255)   'LightCyan1'
-	(209 238 238)   'LightCyan2'
-	(180 205 205)   'LightCyan3'
-	(122 139 139)   'LightCyan4'
-	(255 236 139)   'LightGoldenrod1'
-	(238 220 130)   'LightGoldenrod2'
-	(205 190 112)   'LightGoldenrod3'
-	(139 129  76)   'LightGoldenrod4'
-	(255 174 185)   'LightPink1'
-	(238 162 173)   'LightPink2'
-	(205 140 149)   'LightPink3'
-	(139  95 101)   'LightPink4'
-	(255 160 122)   'LightSalmon1'
-	(238 149 114)   'LightSalmon2'
-	(205 129  98)   'LightSalmon3'
-	(139  87  66)   'LightSalmon4'
-	(176 226 255)   'LightSkyBlue1'
-	(164 211 238)   'LightSkyBlue2'
-	(141 182 205)   'LightSkyBlue3'
-	( 96 123 139)   'LightSkyBlue4'
-	(202 225 255)   'LightSteelBlue1'
-	(188 210 238)   'LightSteelBlue2'
-	(162 181 205)   'LightSteelBlue3'
-	(110 123 139)   'LightSteelBlue4'
-	(255 255 224)   'LightYellow1'
-	(238 238 209)   'LightYellow2'
-	(205 205 180)   'LightYellow3'
-	(139 139 122)   'LightYellow4'
-	( 50 205  50)   'limegreen'
-	(250 240 230)   'linen'
-	(255   0 255)   'magenta'
-	(255   0 255)   'magenta1'
-	(238   0 238)   'magenta2'
-	(205   0 205)   'magenta3'
-	(139   0 139)   'magenta4'
-	(176  48  96)   'maroon'
-	(255  52 179)   'maroon1'
-	(238  48 167)   'maroon2'
-	(205  41 144)   'maroon3'
-	(139  28  98)   'maroon4'
-	(102 205 170)   'mediumaquamarine'
-	(  0   0 205)   'mediumblue'
-	(186  85 211)   'mediumorchid'
-	(147 112 219)   'mediumpurple'
-	( 60 179 113)   'mediumseagreen'
-	(123 104 238)   'mediumslateblue'
-	(  0 250 154)   'mediumspringgreen'
-	( 72 209 204)   'mediumturquoise'
-	(199  21 133)   'mediumvioletred'
-	(224 102 255)   'MediumOrchid1'
-	(209  95 238)   'MediumOrchid2'
-	(180  82 205)   'MediumOrchid3'
-	(122  55 139)   'MediumOrchid4'
-	(171 130 255)   'MediumPurple1'
-	(159 121 238)   'MediumPurple2'
-	(137 104 205)   'MediumPurple3'
-	( 93  71 139)   'MediumPurple4'
-	( 25  25 112)   'midnightblue'
-	(245 255 250)   'mintcream'
-	(255 228 225)   'mistyrose'
-	(255 228 225)   'MistyRose1'
-	(238 213 210)   'MistyRose2'
-	(205 183 181)   'MistyRose3'
-	(139 125 123)   'MistyRose4'
-	(255 228 181)   'moccasin'
-	(255 222 173)   'navajowhite'
-	(255 222 173)   'NavajoWhite1'
-	(238 207 161)   'NavajoWhite2'
-	(205 179 139)   'NavajoWhite3'
-	(139 121  94)   'NavajoWhite4'
-	(  0   0 128)   'navy'
-	(  0   0 128)   'navyblue'
-	(253 245 230)   'oldlace'
-	(107 142  35)   'olivedrab'
-	(192 255  62)   'OliveDrab1'
-	(179 238  58)   'OliveDrab2'
-	(154 205  50)   'OliveDrab3'
-	(105 139  34)   'OliveDrab4'
-	(255 165   0)   'orange'
-	(255 165   0)   'orange1'
-	(238 154   0)   'orange2'
-	(205 133   0)   'orange3'
-	(139  90   0)   'orange4'
-	(255  69   0)   'orangered'
-	(255  69   0)   'OrangeRed1'
-	(238  64   0)   'OrangeRed2'
-	(205  55   0)   'OrangeRed3'
-	(139  37   0)   'OrangeRed4'
-	(218 112 214)   'orchid'
-	(255 131 250)   'orchid1'
-	(238 122 233)   'orchid2'
-	(205 105 201)   'orchid3'
-	(139  71 137)   'orchid4'
-	(238 232 170)   'palegoldenrod'
-	(152 251 152)   'palegreen'
-	(175 238 238)   'paleturquoise'
-	(219 112 147)   'palevioletred'
-	(154 255 154)   'PaleGreen1'
-	(144 238 144)   'PaleGreen2'
-	(124 205 124)   'PaleGreen3'
-	( 84 139  84)   'PaleGreen4'
-	(187 255 255)   'PaleTurquoise1'
-	(174 238 238)   'PaleTurquoise2'
-	(150 205 205)   'PaleTurquoise3'
-	(102 139 139)   'PaleTurquoise4'
-	(255 130 171)   'PaleVioletRed1'
-	(238 121 159)   'PaleVioletRed2'
-	(205 104 137)   'PaleVioletRed3'
-	(139  71  93)   'PaleVioletRed4'
-	(255 239 213)   'papayawhip'
-	(255 218 185)   'peachpuff'
-	(255 218 185)   'PeachPuff1'
-	(238 203 173)   'PeachPuff2'
-	(205 175 149)   'PeachPuff3'
-	(139 119 101)   'PeachPuff4'
-	(205 133  63)   'peru'
-	(255 192 203)   'pink'
-	(255 181 197)   'pink1'
-	(238 169 184)   'pink2'
-	(205 145 158)   'pink3'
-	(139  99 108)   'pink4'
-	(221 160 221)   'plum'
-	(255 187 255)   'plum1'
-	(238 174 238)   'plum2'
-	(205 150 205)   'plum3'
-	(139 102 139)   'plum4'
-	(176 224 230)   'powderblue'
-	(160  32 240)   'purple'
-	(155  48 255)   'purple1'
-	(145  44 238)   'purple2'
-	(125  38 205)   'purple3'
-	( 85  26 139)   'purple4'
-	(255   0   0)   'red'
-	(255   0   0)   'red1'
-	(238   0   0)   'red2'
-	(205   0   0)   'red3'
-	(139   0   0)   'red4'
-	(188 143 143)   'rosybrown'
-	(255 193 193)   'RosyBrown1'
-	(238 180 180)   'RosyBrown2'
-	(205 155 155)   'RosyBrown3'
-	(139 105 105)   'RosyBrown4'
-	( 65 105 225)   'royalblue'
-	( 72 118 255)   'RoyalBlue1'
-	( 67 110 238)   'RoyalBlue2'
-	( 58  95 205)   'RoyalBlue3'
-	( 39  64 139)   'RoyalBlue4'
-	(139  69  19)   'saddlebrown'
-	(250 128 114)   'salmon'
-	(255 140 105)   'salmon1'
-	(238 130  98)   'salmon2'
-	(205 112  84)   'salmon3'
-	(139  76  57)   'salmon4'
-	(244 164  96)   'sandybrown'
-	( 255 206 137)  'scoActiveBackground'
-	( 43  45  49)   'scoActiveForeground'
-	( 254 222 255)  'scoActiveTopShadow'
-	( 172 186 204)  'scoAltBackground'
-	( 203 203 192)  'scoBackground'
-	( 11   0 113)   'scoForeground'
-	( 141 178 215)  'scoHighlight'
-	( 255 240 248)  'scoTopShadow'
-	( 46 139  87)   'seagreen'
-	( 84 255 159)   'SeaGreen1'
-	( 78 238 148)   'SeaGreen2'
-	( 67 205 128)   'SeaGreen3'
-	( 46 139  87)   'SeaGreen4'
-	(255 245 238)   'seashell'
-	(255 245 238)   'seashell1'
-	(238 229 222)   'seashell2'
-	(205 197 191)   'seashell3'
-	(139 134 130)   'seashell4'
-	(142 56 142)    'sgi beet'
-	(197 193 170)   'sgi bright gray'
-	(197 193 170)   'sgi bright grey'
-	(113 198 113)   'sgi chartreuse'
-	( 85  85  85)   'sgi dark gray'
-	( 85  85  85)   'sgi dark grey'
-	(  0   0   0)   'sgi gray 0'
-	(255 255 255)   'sgi gray 100'
-	( 30  30  30)   'sgi gray 12'
-	( 40  40  40)   'sgi gray 16'
-	( 51  51  51)   'sgi gray 20'
-	( 61  61  61)   'sgi gray 24'
-	( 71  71  71)   'sgi gray 28'
-	( 81  81  81)   'sgi gray 32'
-	( 91  91  91)   'sgi gray 36'
-	( 10  10  10)   'sgi gray 4'
-	(102 102 102)   'sgi gray 40'
-	(112 112 112)   'sgi gray 44'
-	(122 122 122)   'sgi gray 48'
-	(132 132 132)   'sgi gray 52'
-	(142 142 142)   'sgi gray 56'
-	(153 153 153)   'sgi gray 60'
-	(163 163 163)   'sgi gray 64'
-	(173 173 173)   'sgi gray 68'
-	(183 183 183)   'sgi gray 72'
-	(193 193 193)   'sgi gray 76'
-	( 20  20  20)   'sgi gray 8'
-	(204 204 204)   'sgi gray 80'
-	(214 214 214)   'sgi gray 84'
-	(224 224 224)   'sgi gray 88'
-	(234 234 234)   'sgi gray 92'
-	(244 244 244)   'sgi gray 96'
-	(  0   0   0)   'sgi grey 0'
-	(255 255 255)   'sgi grey 100'
-	( 30  30  30)   'sgi grey 12'
-	( 40  40  40)   'sgi grey 16'
-	( 51  51  51)   'sgi grey 20'
-	( 61  61  61)   'sgi grey 24'
-	( 71  71  71)   'sgi grey 28'
-	( 81  81  81)   'sgi grey 32'
-	( 91  91  91)   'sgi grey 36'
-	( 10  10  10)   'sgi grey 4'
-	(102 102 102)   'sgi grey 40'
-	(112 112 112)   'sgi grey 44'
-	(122 122 122)   'sgi grey 48'
-	(132 132 132)   'sgi grey 52'
-	(142 142 142)   'sgi grey 56'
-	(153 153 153)   'sgi grey 60'
-	(163 163 163)   'sgi grey 64'
-	(173 173 173)   'sgi grey 68'
-	(183 183 183)   'sgi grey 72'
-	(193 193 193)   'sgi grey 76'
-	( 20  20  20)   'sgi grey 8'
-	(204 204 204)   'sgi grey 80'
-	(214 214 214)   'sgi grey 84'
-	(224 224 224)   'sgi grey 88'
-	(234 234 234)   'sgi grey 92'
-	(244 244 244)   'sgi grey 96'
-	(125 158 192)   'sgi light blue'
-	(170 170 170)   'sgi light gray'
-	(170 170 170)   'sgi light grey'
-	(132 132 132)   'sgi medium gray'
-	(132 132 132)   'sgi medium grey'
-	(142 142  56)   'sgi olive drab'
-	(198 113 113)   'sgi salmon'
-	(113 113 198)   'sgi slate blue'
-	( 56 142 142)   'sgi teal'
-	( 40  40  40)   'sgi very dark gray'
-	( 40  40  40)   'sgi very dark grey'
-	(214 214 214)   'sgi very light gray'
-	(214 214 214)   'sgi very light grey'
-	(142 56 142)    'SGIBeet'
-	(197 193 170)   'SGIBrightGray'
-	(197 193 170)   'SGIBrightGrey'
-	(113 198 113)   'SGIChartreuse'
-	( 85  85  85)   'SGIDarkGray'
-	( 85  85  85)   'SGIDarkGrey'
-	(  0   0   0)   'SGIGray0'
-	(255 255 255)   'SGIGray100'
-	( 30  30  30)   'SGIGray12'
-	( 40  40  40)   'SGIGray16'
-	( 51  51  51)   'SGIGray20'
-	( 61  61  61)   'SGIGray24'
-	( 71  71  71)   'SGIGray28'
-	( 81  81  81)   'SGIGray32'
-	( 91  91  91)   'SGIGray36'
-	( 10  10  10)   'SGIGray4'
-	(102 102 102)   'SGIGray40'
-	(112 112 112)   'SGIGray44'
-	(122 122 122)   'SGIGray48'
-	(132 132 132)   'SGIGray52'
-	(142 142 142)   'SGIGray56'
-	(153 153 153)   'SGIGray60'
-	(163 163 163)   'SGIGray64'
-	(173 173 173)   'SGIGray68'
-	(183 183 183)   'SGIGray72'
-	(193 193 193)   'SGIGray76'
-	( 20  20  20)   'SGIGray8'
-	(204 204 204)   'SGIGray80'
-	(214 214 214)   'SGIGray84'
-	(224 224 224)   'SGIGray88'
-	(234 234 234)   'SGIGray92'
-	(244 244 244)   'SGIGray96'
-	(  0   0   0)   'SGIGrey0'
-	(255 255 255)   'SGIGrey100'
-	( 30  30  30)   'SGIGrey12'
-	( 40  40  40)   'SGIGrey16'
-	( 51  51  51)   'SGIGrey20'
-	( 61  61  61)   'SGIGrey24'
-	( 71  71  71)   'SGIGrey28'
-	( 81  81  81)   'SGIGrey32'
-	( 91  91  91)   'SGIGrey36'
-	( 10  10  10)   'SGIGrey4'
-	(102 102 102)   'SGIGrey40'
-	(112 112 112)   'SGIGrey44'
-	(122 122 122)   'SGIGrey48'
-	(132 132 132)   'SGIGrey52'
-	(142 142 142)   'SGIGrey56'
-	(153 153 153)   'SGIGrey60'
-	(163 163 163)   'SGIGrey64'
-	(173 173 173)   'SGIGrey68'
-	(183 183 183)   'SGIGrey72'
-	(193 193 193)   'SGIGrey76'
-	( 20  20  20)   'SGIGrey8'
-	(204 204 204)   'SGIGrey80'
-	(214 214 214)   'SGIGrey84'
-	(224 224 224)   'SGIGrey88'
-	(234 234 234)   'SGIGrey92'
-	(244 244 244)   'SGIGrey96'
-	(125 158 192)   'SGILightBlue'
-	(170 170 170)   'SGILightGray'
-	(170 170 170)   'SGILightGrey'
-	(132 132 132)   'SGIMediumGray'
-	(132 132 132)   'SGIMediumGrey'
-	(142 142  56)   'SGIOliveDrab'
-	(198 113 113)   'SGISalmon'
-	(113 113 198)   'SGISlateBlue'
-	( 56 142 142)   'SGITeal'
-	( 40  40  40)   'SGIVeryDarkGray'
-	( 40  40  40)   'SGIVeryDarkGrey'
-	(214 214 214)   'SGIVeryLightGray'
-	(214 214 214)   'SGIVeryLightGrey'
-	(160  82  45)   'sienna'
-	(255 130  71)   'sienna1'
-	(238 121  66)   'sienna2'
-	(205 104  57)   'sienna3'
-	(139  71  38)   'sienna4'
-	(135 206 235)   'skyblue'
-	(135 206 255)   'SkyBlue1'
-	(126 192 238)   'SkyBlue2'
-	(108 166 205)   'SkyBlue3'
-	( 74 112 139)   'SkyBlue4'
-	(112 128 144)   'slategray'
-	(112 128 144)   'slategrey'
-	(106  90 205)   'slateblue'
-	(131 111 255)   'SlateBlue1'
-	(122 103 238)   'SlateBlue2'
-	(105  89 205)   'SlateBlue3'
-	( 71  60 139)   'SlateBlue4'
-	(198 226 255)   'SlateGray1'
-	(185 211 238)   'SlateGray2'
-	(159 182 205)   'SlateGray3'
-	(108 123 139)   'SlateGray4'
-	(255 250 250)   'snow'
-	(255 250 250)   'snow1'
-	(238 233 233)   'snow2'
-	(205 201 201)   'snow3'
-	(139 137 137)   'snow4'
-	(  0 255 127)   'springgreen'
-	(  0 255 127)   'SpringGreen1'
-	(  0 238 118)   'SpringGreen2'
-	(  0 205 102)   'SpringGreen3'
-	(  0 139  69)   'SpringGreen4'
-	( 70 130 180)   'steelblue'
-	( 99 184 255)   'SteelBlue1'
-	( 92 172 238)   'SteelBlue2'
-	( 79 148 205)   'SteelBlue3'
-	( 54 100 139)   'SteelBlue4'
-	(210 180 140)   'tan'
-	(255 165  79)   'tan1'
-	(238 154  73)   'tan2'
-	(205 133  63)   'tan3'
-	(139  90  43)   'tan4'
-	(216 191 216)   'thistle'
-	(255 225 255)   'thistle1'
-	(238 210 238)   'thistle2'
-	(205 181 205)   'thistle3'
-	(139 123 139)   'thistle4'
-	(255  99  71)   'tomato'
-	(255  99  71)   'tomato1'
-	(238  92  66)   'tomato2'
-	(205  79  57)   'tomato3'
-	(139  54  38)   'tomato4'
-	( 64 224 208)   'turquoise'
-	(  0 245 255)   'turquoise1'
-	(  0 229 238)   'turquoise2'
-	(  0 197 205)   'turquoise3'
-	(  0 134 139)   'turquoise4'
-	(238 130 238)   'violet'
-	(208  32 144)   'violetred'
-	(255  62 150)   'VioletRed1'
-	(238  58 140)   'VioletRed2'
-	(205  50 120)   'VioletRed3'
-	(139  34  82)   'VioletRed4'
-	(245 222 179)   'wheat'
-	(255 231 186)   'wheat1'
-	(238 216 174)   'wheat2'
-	(205 186 150)   'wheat3'
-	(139 126 102)   'wheat4'
-	(255 255 255)   'white'
-	(245 245 245)   'whitesmoke'
-	(255 255   0)   'yellow'
-	(154 205  50)   'yellowgreen'
-	(255 255   0)   'yellow1'
-	(238 238   0)   'yellow2'
-	(205 205   0)   'yellow3'
-	(139 139   0)   'yellow4'
-    ) pairWiseDo:[ :value :name |
-	StandardColorValues at:name put:value
-    ].
+    StandardColorValues := Dictionary
+	withKeysAndValues:#(
+	    'aliceblue'     (240 248 255)
+	    'antiquewhite'  (250 235 215)
+	    'AntiqueWhite1' (255 239 219)
+	    'AntiqueWhite2' (238 223 204)
+	    'AntiqueWhite3' (205 192 176)
+	    'AntiqueWhite4' (139 131 120)
+	    'aquamarine'    (127 255 212)
+	    'aquamarine1'   (127 255 212)
+	    'aquamarine2'   (118 238 198)
+	    'aquamarine3'   (102 205 170)
+	    'aquamarine4'   (69 139 116)
+	    'azure'         (240 255 255)
+	    'azure1'        (240 255 255)
+	    'azure2'        (224 238 238)
+	    'azure3'        (193 205 205)
+	    'azure4'        (131 139 139)
+	    'beige'         (245 245 220)
+	    'bisque'        (255 228 196)
+	    'bisque1'       (255 228 196)
+	    'bisque2'       (238 213 183)
+	    'bisque3'       (205 183 158)
+	    'bisque4'       (139 125 107)
+	    'black'         (0 0 0)
+	    'blanchedalmond'        (255 235 205)
+	    'blue'          (0 0 255)
+	    'blueviolet'    (138 43 226)
+	    'blue1'         (0 0 255)
+	    'blue2'         (0 0 238)
+	    'blue3'         (0 0 205)
+	    'blue4'         (0 0 139)
+	    'brown'         (165 42 42)
+	    'brown1'        (255 64 64)
+	    'brown2'        (238 59 59)
+	    'brown3'        (205 51 51)
+	    'brown4'        (139 35 35)
+	    'burlywood'     (222 184 135)
+	    'burlywood1'    (255 211 155)
+	    'burlywood2'    (238 197 145)
+	    'burlywood3'    (205 170 125)
+	    'burlywood4'    (139 115 85)
+	    'cadetblue'     (95 158 160)
+	    'CadetBlue1'    (152 245 255)
+	    'CadetBlue2'    (142 229 238)
+	    'CadetBlue3'    (122 197 205)
+	    'CadetBlue4'    (83 134 139)
+	    'chartreuse'    (127 255 0)
+	    'chartreuse1'   (127 255 0)
+	    'chartreuse2'   (118 238 0)
+	    'chartreuse3'   (102 205 0)
+	    'chartreuse4'   (69 139 0)
+	    'chocolate'     (210 105 30)
+	    'chocolate1'    (255 127 36)
+	    'chocolate2'    (238 118 33)
+	    'chocolate3'    (205 102 29)
+	    'chocolate4'    (139 69 19)
+	    'coral'         (255 127 80)
+	    'coral1'        (255 114 86)
+	    'coral2'        (238 106 80)
+	    'coral3'        (205 91 69)
+	    'coral4'        (139 62 47)
+	    'cornflowerblue'        (100 149 237)
+	    'cornsilk'      (255 248 220)
+	    'cornsilk1'     (255 248 220)
+	    'cornsilk2'     (238 232 205)
+	    'cornsilk3'     (205 200 177)
+	    'cornsilk4'     (139 136 120)
+	    'cyan'          (0 255 255)
+	    'cyan1'         (0 255 255)
+	    'cyan2'         (0 238 238)
+	    'cyan3'         (0 205 205)
+	    'cyan4'         (0 139 139)
+	    'darkblue'      (0 0 139)
+	    'darkcyan'      (0 139 139)
+	    'darkgoldenrod' (184 134 11)
+	    'darkgray'      (169 169 169)
+	    'darkgreen'     (0 100 0)
+	    'darkgrey'      (169 169 169)
+	    'darkkhaki'     (189 183 107)
+	    'darkmagenta'   (139 0 139)
+	    'darkolivegreen'        (85 107 47)
+	    'darkorange'    (255 140 0)
+	    'darkorchid'    (153 50 204)
+	    'darkred'       (139 0 0)
+	    'darksalmon'    (233 150 122)
+	    'darkseagreen'  (143 188 143)
+	    'darkslateblue' (72 61 139)
+	    'darkslategray' (47 79 79)
+	    'darkslategrey' (47 79 79)
+	    'darkturquoise' (0 206 209)
+	    'darkviolet'    (148 0 211)
+	    'DarkGoldenrod1'        (255 185 15)
+	    'DarkGoldenrod2'        (238 173 14)
+	    'DarkGoldenrod3'        (205 149 12)
+	    'DarkGoldenrod4'        (139 101 8)
+	    'DarkOliveGreen1'       (202 255 112)
+	    'DarkOliveGreen2'       (188 238 104)
+	    'DarkOliveGreen3'       (162 205 90)
+	    'DarkOliveGreen4'       (110 139 61)
+	    'DarkOrange1'   (255 127 0)
+	    'DarkOrange2'   (238 118 0)
+	    'DarkOrange3'   (205 102 0)
+	    'DarkOrange4'   (139 69 0)
+	    'DarkOrchid1'   (191 62 255)
+	    'DarkOrchid2'   (178 58 238)
+	    'DarkOrchid3'   (154 50 205)
+	    'DarkOrchid4'   (104 34 139)
+	    'DarkSeaGreen1' (193 255 193)
+	    'DarkSeaGreen2' (180 238 180)
+	    'DarkSeaGreen3' (155 205 155)
+	    'DarkSeaGreen4' (105 139 105)
+	    'DarkSlateGray1'        (151 255 255)
+	    'DarkSlateGray2'        (141 238 238)
+	    'DarkSlateGray3'        (121 205 205)
+	    'DarkSlateGray4'        (82 139 139)
+	    'deeppink'      (255 20 147)
+	    'deepskyblue'   (0 191 255)
+	    'DeepPink'      (255 20 147)
+	    'DeepPink1'     (255 20 147)
+	    'DeepPink2'     (238 18 137)
+	    'DeepPink3'     (205 16 118)
+	    'DeepPink4'     (139 10 80)
+	    'DeepSkyBlue1'  (0 191 255)
+	    'DeepSkyBlue2'  (0 178 238)
+	    'DeepSkyBlue3'  (0 154 205)
+	    'DeepSkyBlue4'  (0 104 139)
+	    'dimgray'       (105 105 105)
+	    'dimgrey'       (105 105 105)
+	    'dodgerblue'    (30 144 255)
+	    'DodgerBlue1'   (30 144 255)
+	    'DodgerBlue2'   (28 134 238)
+	    'DodgerBlue3'   (24 116 205)
+	    'DodgerBlue4'   (16 78 139)
+	    'firebrick'     (178 34 34)
+	    'firebrick1'    (255 48 48)
+	    'firebrick2'    (238 44 44)
+	    'firebrick3'    (205 38 38)
+	    'firebrick4'    (139 26 26)
+	    'floralwhite'   (255 250 240)
+	    'forestgreen'   (34 139 34)
+	    'gainsboro'     (220 220 220)
+	    'ghostwhite'    (248 248 255)
+	    'gold'          (255 215 0)
+	    'gold1'         (255 215 0)
+	    'gold2'         (238 201 0)
+	    'gold3'         (205 173 0)
+	    'gold4'         (139 117 0)
+	    'goldenrod'     (218 165 32)
+	    'goldenrod1'    (255 193 37)
+	    'goldenrod2'    (238 180 34)
+	    'goldenrod3'    (205 155 29)
+	    'goldenrod4'    (139 105 20)
+	    'grey'          (192 192 192)
+	    'grey0'         (0 0 0)
+	    'grey1'         (3 3 3)
+	    'grey10'        (26 26 26)
+	    'grey100'       (255 255 255)
+	    'grey11'        (28 28 28)
+	    'grey12'        (31 31 31)
+	    'grey13'        (33 33 33)
+	    'grey14'        (36 36 36)
+	    'grey15'        (38 38 38)
+	    'grey16'        (41 41 41)
+	    'grey17'        (43 43 43)
+	    'grey18'        (46 46 46)
+	    'grey19'        (48 48 48)
+	    'grey2'         (5 5 5)
+	    'grey20'        (51 51 51)
+	    'grey21'        (54 54 54)
+	    'grey22'        (56 56 56)
+	    'grey23'        (59 59 59)
+	    'grey24'        (61 61 61)
+	    'grey25'        (64 64 64)
+	    'grey26'        (66 66 66)
+	    'grey27'        (69 69 69)
+	    'grey28'        (71 71 71)
+	    'grey29'        (74 74 74)
+	    'grey3'         (8 8 8)
+	    'grey30'        (77 77 77)
+	    'grey31'        (79 79 79)
+	    'grey32'        (82 82 82)
+	    'grey33'        (84 84 84)
+	    'grey34'        (87 87 87)
+	    'grey35'        (89 89 89)
+	    'grey36'        (92 92 92)
+	    'grey37'        (94 94 94)
+	    'grey38'        (97 97 97)
+	    'grey39'        (99 99 99)
+	    'grey4'         (10 10 10)
+	    'grey40'        (102 102 102)
+	    'grey41'        (105 105 105)
+	    'grey42'        (107 107 107)
+	    'grey43'        (110 110 110)
+	    'grey44'        (112 112 112)
+	    'grey45'        (115 115 115)
+	    'grey46'        (117 117 117)
+	    'grey47'        (120 120 120)
+	    'grey48'        (122 122 122)
+	    'grey49'        (125 125 125)
+	    'grey5'         (13 13 13)
+	    'grey50'        (127 127 127)
+	    'grey51'        (130 130 130)
+	    'grey52'        (133 133 133)
+	    'grey53'        (135 135 135)
+	    'grey54'        (138 138 138)
+	    'grey55'        (140 140 140)
+	    'grey56'        (143 143 143)
+	    'grey57'        (145 145 145)
+	    'grey58'        (148 148 148)
+	    'grey59'        (150 150 150)
+	    'grey6'         (15 15 15)
+	    'grey60'        (153 153 153)
+	    'grey61'        (156 156 156)
+	    'grey62'        (158 158 158)
+	    'grey63'        (161 161 161)
+	    'grey64'        (163 163 163)
+	    'grey65'        (166 166 166)
+	    'grey66'        (168 168 168)
+	    'grey67'        (171 171 171)
+	    'grey68'        (173 173 173)
+	    'grey69'        (176 176 176)
+	    'grey7'         (18 18 18)
+	    'grey70'        (179 179 179)
+	    'grey71'        (181 181 181)
+	    'grey72'        (184 184 184)
+	    'grey73'        (186 186 186)
+	    'grey74'        (189 189 189)
+	    'grey75'        (191 191 191)
+	    'grey76'        (194 194 194)
+	    'grey77'        (196 196 196)
+	    'grey78'        (199 199 199)
+	    'grey79'        (201 201 201)
+	    'grey8'         (20 20 20)
+	    'grey80'        (204 204 204)
+	    'grey81'        (207 207 207)
+	    'grey82'        (209 209 209)
+	    'grey83'        (212 212 212)
+	    'grey84'        (214 214 214)
+	    'grey85'        (217 217 217)
+	    'grey86'        (219 219 219)
+	    'grey87'        (222 222 222)
+	    'grey88'        (224 224 224)
+	    'grey89'        (227 227 227)
+	    'grey9'         (23 23 23)
+	    'grey90'        (229 229 229)
+	    'grey91'        (232 232 232)
+	    'grey92'        (235 235 235)
+	    'grey93'        (237 237 237)
+	    'grey94'        (240 240 240)
+	    'grey95'        (242 242 242)
+	    'grey96'        (245 245 245)
+	    'grey97'        (247 247 247)
+	    'grey98'        (250 250 250)
+	    'grey99'        (252 252 252)
+	    'gray'          (192 192 192)
+	    'gray0'         (0 0 0)
+	    'gray1'         (3 3 3)
+	    'gray10'        (26 26 26)
+	    'gray100'       (255 255 255)
+	    'gray11'        (28 28 28)
+	    'gray12'        (31 31 31)
+	    'gray13'        (33 33 33)
+	    'gray14'        (36 36 36)
+	    'gray15'        (38 38 38)
+	    'gray16'        (41 41 41)
+	    'gray17'        (43 43 43)
+	    'gray18'        (46 46 46)
+	    'gray19'        (48 48 48)
+	    'gray2'         (5 5 5)
+	    'gray20'        (51 51 51)
+	    'gray21'        (54 54 54)
+	    'gray22'        (56 56 56)
+	    'gray23'        (59 59 59)
+	    'gray24'        (61 61 61)
+	    'gray25'        (64 64 64)
+	    'gray26'        (66 66 66)
+	    'gray27'        (69 69 69)
+	    'gray28'        (71 71 71)
+	    'gray29'        (74 74 74)
+	    'gray3'         (8 8 8)
+	    'gray30'        (77 77 77)
+	    'gray31'        (79 79 79)
+	    'gray32'        (82 82 82)
+	    'gray33'        (84 84 84)
+	    'gray34'        (87 87 87)
+	    'gray35'        (89 89 89)
+	    'gray36'        (92 92 92)
+	    'gray37'        (94 94 94)
+	    'gray38'        (97 97 97)
+	    'gray39'        (99 99 99)
+	    'gray4'         (10 10 10)
+	    'gray40'        (102 102 102)
+	    'gray41'        (105 105 105)
+	    'gray42'        (107 107 107)
+	    'gray43'        (110 110 110)
+	    'gray44'        (112 112 112)
+	    'gray45'        (115 115 115)
+	    'gray46'        (117 117 117)
+	    'gray47'        (120 120 120)
+	    'gray48'        (122 122 122)
+	    'gray49'        (125 125 125)
+	    'gray5'         (13 13 13)
+	    'gray50'        (127 127 127)
+	    'gray51'        (130 130 130)
+	    'gray52'        (133 133 133)
+	    'gray53'        (135 135 135)
+	    'gray54'        (138 138 138)
+	    'gray55'        (140 140 140)
+	    'gray56'        (143 143 143)
+	    'gray57'        (145 145 145)
+	    'gray58'        (148 148 148)
+	    'gray59'        (150 150 150)
+	    'gray6'         (15 15 15)
+	    'gray60'        (153 153 153)
+	    'gray61'        (156 156 156)
+	    'gray62'        (158 158 158)
+	    'gray63'        (161 161 161)
+	    'gray64'        (163 163 163)
+	    'gray65'        (166 166 166)
+	    'gray66'        (168 168 168)
+	    'gray67'        (171 171 171)
+	    'gray68'        (173 173 173)
+	    'gray69'        (176 176 176)
+	    'gray7'         (18 18 18)
+	    'gray70'        (179 179 179)
+	    'gray71'        (181 181 181)
+	    'gray72'        (184 184 184)
+	    'gray73'        (186 186 186)
+	    'gray74'        (189 189 189)
+	    'gray75'        (191 191 191)
+	    'gray76'        (194 194 194)
+	    'gray77'        (196 196 196)
+	    'gray78'        (199 199 199)
+	    'gray79'        (201 201 201)
+	    'gray8'         (20 20 20)
+	    'gray80'        (204 204 204)
+	    'gray81'        (207 207 207)
+	    'gray82'        (209 209 209)
+	    'gray83'        (212 212 212)
+	    'gray84'        (214 214 214)
+	    'gray85'        (217 217 217)
+	    'gray86'        (219 219 219)
+	    'gray87'        (222 222 222)
+	    'gray88'        (224 224 224)
+	    'gray89'        (227 227 227)
+	    'gray9'         (23 23 23)
+	    'gray90'        (229 229 229)
+	    'gray91'        (232 232 232)
+	    'gray92'        (235 235 235)
+	    'gray93'        (237 237 237)
+	    'gray94'        (240 240 240)
+	    'gray95'        (242 242 242)
+	    'gray96'        (245 245 245)
+	    'gray97'        (247 247 247)
+	    'gray98'        (250 250 250)
+	    'gray99'        (252 252 252)
+	    'green'         (0 255 0)
+	    'greenyellow'   (173 255 47)
+	    'green1'        (0 255 0)
+	    'green2'        (0 238 0)
+	    'green3'        (0 205 0)
+	    'green4'        (0 139 0)
+	    'honeydew'      (240 255 240)
+	    'honeydew1'     (240 255 240)
+	    'honeydew2'     (224 238 224)
+	    'honeydew3'     (193 205 193)
+	    'honeydew4'     (131 139 131)
+	    'hotpink'       (255 105 180)
+	    'HotPink1'      (255 110 180)
+	    'HotPink2'      (238 106 167)
+	    'HotPink3'      (205 96 144)
+	    'HotPink4'      (139 58 98)
+	    'indianred'     (205 92 92)
+	    'IndianRed1'    (255 106 106)
+	    'IndianRed2'    (238 99 99)
+	    'IndianRed3'    (205 85 85)
+	    'IndianRed4'    (139 58 58)
+	    'ivory'         (255 255 240)
+	    'ivory1'        (255 255 240)
+	    'ivory2'        (238 238 224)
+	    'ivory3'        (205 205 193)
+	    'ivory4'        (139 139 131)
+	    'khaki'         (240 230 140)
+	    'khaki1'        (255 246 143)
+	    'khaki2'        (238 230 133)
+	    'khaki3'        (205 198 115)
+	    'khaki4'        (139 134 78)
+	    'lavender'      (230 230 250)
+	    'lavenderblush'         (255 240 245)
+	    'LavenderBlush1'        (255 240 245)
+	    'LavenderBlush2'        (238 224 229)
+	    'LavenderBlush3'        (205 193 197)
+	    'LavenderBlush4'        (139 131 134)
+	    'lawngreen'     (124 252 0)
+	    'lemonchiffon'  (255 250 205)
+	    'LemonChiffon1'         (255 250 205)
+	    'LemonChiffon2'         (238 233 191)
+	    'LemonChiffon3'         (205 201 165)
+	    'LemonChiffon4'         (139 137 112)
+	    'lightblue'     (173 216 230)
+	    'lightcoral'    (240 128 128)
+	    'lightcyan'     (224 255 255)
+	    'lightgoldenrod'        (238 221 130)
+	    'lightgoldenrodyellow'  (250 250 210)
+	    'lightgray'     (211 211 211)
+	    'lightgreen'    (144 238 144)
+	    'lightgrey'     (211 211 211)
+	    'lightpink'     (255 182 193)
+	    'lightsalmon'   (255 160 122)
+	    'lightseagreen' (32 178 170)
+	    'lightskyblue'  (135 206 250)
+	    'lightslateblue'        (132 112 255)
+	    'lightslategray'        (119 136 153)
+	    'lightslategrey'        (119 136 153)
+	    'lightsteelblue'        (176 196 222)
+	    'lightyellow'   (255 255 224)
+	    'LightBlue1'    (191 239 255)
+	    'LightBlue2'    (178 223 238)
+	    'LightBlue3'    (154 192 205)
+	    'LightBlue4'    (104 131 139)
+	    'LightCyan1'    (224 255 255)
+	    'LightCyan2'    (209 238 238)
+	    'LightCyan3'    (180 205 205)
+	    'LightCyan4'    (122 139 139)
+	    'LightGoldenrod1'       (255 236 139)
+	    'LightGoldenrod2'       (238 220 130)
+	    'LightGoldenrod3'       (205 190 112)
+	    'LightGoldenrod4'       (139 129 76)
+	    'LightPink1'    (255 174 185)
+	    'LightPink2'    (238 162 173)
+	    'LightPink3'    (205 140 149)
+	    'LightPink4'    (139 95 101)
+	    'LightSalmon1'  (255 160 122)
+	    'LightSalmon2'  (238 149 114)
+	    'LightSalmon3'  (205 129 98)
+	    'LightSalmon4'  (139 87 66)
+	    'LightSkyBlue1'         (176 226 255)
+	    'LightSkyBlue2'         (164 211 238)
+	    'LightSkyBlue3'         (141 182 205)
+	    'LightSkyBlue4'         (96 123 139)
+	    'LightSteelBlue1'       (202 225 255)
+	    'LightSteelBlue2'       (188 210 238)
+	    'LightSteelBlue3'       (162 181 205)
+	    'LightSteelBlue4'       (110 123 139)
+	    'LightYellow1'  (255 255 224)
+	    'LightYellow2'  (238 238 209)
+	    'LightYellow3'  (205 205 180)
+	    'LightYellow4'  (139 139 122)
+	    'limegreen'     (50 205 50)
+	    'linen'         (250 240 230)
+	    'magenta'       (255 0 255)
+	    'magenta1'      (255 0 255)
+	    'magenta2'      (238 0 238)
+	    'magenta3'      (205 0 205)
+	    'magenta4'      (139 0 139)
+	    'maroon'        (176 48 96)
+	    'maroon1'       (255 52 179)
+	    'maroon2'       (238 48 167)
+	    'maroon3'       (205 41 144)
+	    'maroon4'       (139 28 98)
+	    'mediumaquamarine'      (102 205 170)
+	    'mediumblue'    (0 0 205)
+	    'mediumorchid'  (186 85 211)
+	    'mediumpurple'  (147 112 219)
+	    'mediumseagreen'        (60 179 113)
+	    'mediumslateblue'       (123 104 238)
+	    'mediumspringgreen'     (0 250 154)
+	    'mediumturquoise'       (72 209 204)
+	    'mediumvioletred'       (199 21 133)
+	    'MediumOrchid1'         (224 102 255)
+	    'MediumOrchid2' (209 95 238)
+	    'MediumOrchid3' (180 82 205)
+	    'MediumOrchid4' (122 55 139)
+	    'MediumPurple1' (171 130 255)
+	    'MediumPurple2' (159 121 238)
+	    'MediumPurple3' (137 104 205)
+	    'MediumPurple4' (93 71 139)
+	    'midnightblue'  (25 25 112)
+	    'mintcream'     (245 255 250)
+	    'mistyrose'     (255 228 225)
+	    'MistyRose1'    (255 228 225)
+	    'MistyRose2'    (238 213 210)
+	    'MistyRose3'    (205 183 181)
+	    'MistyRose4'    (139 125 123)
+	    'moccasin'      (255 228 181)
+	    'navajowhite'   (255 222 173)
+	    'NavajoWhite1'  (255 222 173)
+	    'NavajoWhite2'  (238 207 161)
+	    'NavajoWhite3'  (205 179 139)
+	    'NavajoWhite4'  (139 121 94)
+	    'navy'          (0 0 128)
+	    'navyblue'      (0 0 128)
+	    'oldlace'       (253 245 230)
+	    'olivedrab'     (107 142 35)
+	    'OliveDrab1'    (192 255 62)
+	    'OliveDrab2'    (179 238 58)
+	    'OliveDrab3'    (154 205 50)
+	    'OliveDrab4'    (105 139 34)
+	    'orange'        (255 165 0)
+	    'orange1'       (255 165 0)
+	    'orange2'       (238 154 0)
+	    'orange3'       (205 133 0)
+	    'orange4'       (139 90 0)
+	    'orangered'     (255 69 0)
+	    'OrangeRed1'    (255 69 0)
+	    'OrangeRed2'    (238 64 0)
+	    'OrangeRed3'    (205 55 0)
+	    'OrangeRed4'    (139 37 0)
+	    'orchid'        (218 112 214)
+	    'orchid1'       (255 131 250)
+	    'orchid2'       (238 122 233)
+	    'orchid3'       (205 105 201)
+	    'orchid4'       (139 71 137)
+	    'palegoldenrod' (238 232 170)
+	    'palegreen'     (152 251 152)
+	    'paleturquoise' (175 238 238)
+	    'palevioletred' (219 112 147)
+	    'PaleGreen1'    (154 255 154)
+	    'PaleGreen2'    (144 238 144)
+	    'PaleGreen3'    (124 205 124)
+	    'PaleGreen4'    (84 139 84)
+	    'PaleTurquoise1'        (187 255 255)
+	    'PaleTurquoise2'        (174 238 238)
+	    'PaleTurquoise3'        (150 205 205)
+	    'PaleTurquoise4'        (102 139 139)
+	    'PaleVioletRed1'        (255 130 171)
+	    'PaleVioletRed2'        (238 121 159)
+	    'PaleVioletRed3'        (205 104 137)
+	    'PaleVioletRed4'        (139 71 93)
+	    'papayawhip'    (255 239 213)
+	    'peachpuff'     (255 218 185)
+	    'PeachPuff1'    (255 218 185)
+	    'PeachPuff2'    (238 203 173)
+	    'PeachPuff3'    (205 175 149)
+	    'PeachPuff4'    (139 119 101)
+	    'peru'  (205 133 63)
+	    'pink'  (255 192 203)
+	    'pink1' (255 181 197)
+	    'pink2' (238 169 184)
+	    'pink3' (205 145 158)
+	    'pink4' (139 99 108)
+	    'plum'  (221 160 221)
+	    'plum1' (255 187 255)
+	    'plum2' (238 174 238)
+	    'plum3' (205 150 205)
+	    'plum4' (139 102 139)
+	    'powderblue'    (176 224 230)
+	    'purple'        (160 32 240)
+	    'purple1'       (155 48 255)
+	    'purple2'       (145 44 238)
+	    'purple3'       (125 38 205)
+	    'purple4'       (85 26 139)
+	    'red'   (255 0 0)
+	    'red1'  (255 0 0)
+	    'red2'  (238 0 0)
+	    'red3'  (205 0 0)
+	    'red4'  (139 0 0)
+	    'rosybrown'     (188 143 143)
+	    'RosyBrown1'    (255 193 193)
+	    'RosyBrown2'    (238 180 180)
+	    'RosyBrown3'    (205 155 155)
+	    'RosyBrown4'    (139 105 105)
+	    'royalblue'     (65 105 225)
+	    'RoyalBlue1'    (72 118 255)
+	    'RoyalBlue2'    (67 110 238)
+	    'RoyalBlue3'    (58 95 205)
+	    'RoyalBlue4'    (39 64 139)
+	    'saddlebrown'   (139 69 19)
+	    'salmon'        (250 128 114)
+	    'salmon1'       (255 140 105)
+	    'salmon2'       (238 130 98)
+	    'salmon3'       (205 112 84)
+	    'salmon4'       (139 76 57)
+	    'sandybrown'    (244 164 96)
+	    'scoActiveBackground'   (255 206 137)
+	    'scoActiveForeground'   (43 45 49)
+	    'scoActiveTopShadow'    (254 222 255)
+	    'scoAltBackground'      (172 186 204)
+	    'scoBackground' (203 203 192)
+	    'scoForeground' (11 0 113)
+	    'scoHighlight'  (141 178 215)
+	    'scoTopShadow'  (255 240 248)
+	    'seagreen'      (46 139 87)
+	    'SeaGreen1'     (84 255 159)
+	    'SeaGreen2'     (78 238 148)
+	    'SeaGreen3'     (67 205 128)
+	    'SeaGreen4'     (46 139 87)
+	    'seashell'      (255 245 238)
+	    'seashell1'     (255 245 238)
+	    'seashell2'     (238 229 222)
+	    'seashell3'     (205 197 191)
+	    'seashell4'     (139 134 130)
+	    'sgi beet'      (142 56 142)
+	    'sgi bright gray'       (197 193 170)
+	    'sgi bright grey'       (197 193 170)
+	    'sgi chartreuse'        (113 198 113)
+	    'sgi dark gray' (85 85 85)
+	    'sgi dark grey' (85 85 85)
+	    'sgi gray 0'    (0 0 0)
+	    'sgi gray 100'  (255 255 255)
+	    'sgi gray 12'   (30 30 30)
+	    'sgi gray 16'   (40 40 40)
+	    'sgi gray 20'   (51 51 51)
+	    'sgi gray 24'   (61 61 61)
+	    'sgi gray 28'   (71 71 71)
+	    'sgi gray 32'   (81 81 81)
+	    'sgi gray 36'   (91 91 91)
+	    'sgi gray 4'    (10 10 10)
+	    'sgi gray 40'   (102 102 102)
+	    'sgi gray 44'   (112 112 112)
+	    'sgi gray 48'   (122 122 122)
+	    'sgi gray 52'   (132 132 132)
+	    'sgi gray 56'   (142 142 142)
+	    'sgi gray 60'   (153 153 153)
+	    'sgi gray 64'   (163 163 163)
+	    'sgi gray 68'   (173 173 173)
+	    'sgi gray 72'   (183 183 183)
+	    'sgi gray 76'   (193 193 193)
+	    'sgi gray 8'    (20 20 20)
+	    'sgi gray 80'   (204 204 204)
+	    'sgi gray 84'   (214 214 214)
+	    'sgi gray 88'   (224 224 224)
+	    'sgi gray 92'   (234 234 234)
+	    'sgi gray 96'   (244 244 244)
+	    'sgi grey 0'    (0 0 0)
+	    'sgi grey 100'  (255 255 255)
+	    'sgi grey 12'   (30 30 30)
+	    'sgi grey 16'   (40 40 40)
+	    'sgi grey 20'   (51 51 51)
+	    'sgi grey 24'   (61 61 61)
+	    'sgi grey 28'   (71 71 71)
+	    'sgi grey 32'   (81 81 81)
+	    'sgi grey 36'   (91 91 91)
+	    'sgi grey 4'    (10 10 10)
+	    'sgi grey 40'   (102 102 102)
+	    'sgi grey 44'   (112 112 112)
+	    'sgi grey 48'   (122 122 122)
+	    'sgi grey 52'   (132 132 132)
+	    'sgi grey 56'   (142 142 142)
+	    'sgi grey 60'   (153 153 153)
+	    'sgi grey 64'   (163 163 163)
+	    'sgi grey 68'   (173 173 173)
+	    'sgi grey 72'   (183 183 183)
+	    'sgi grey 76'   (193 193 193)
+	    'sgi grey 8'    (20 20 20)
+	    'sgi grey 80'   (204 204 204)
+	    'sgi grey 84'   (214 214 214)
+	    'sgi grey 88'   (224 224 224)
+	    'sgi grey 92'   (234 234 234)
+	    'sgi grey 96'   (244 244 244)
+	    'sgi light blue'        (125 158 192)
+	    'sgi light gray'        (170 170 170)
+	    'sgi light grey'        (170 170 170)
+	    'sgi medium gray'       (132 132 132)
+	    'sgi medium grey'       (132 132 132)
+	    'sgi olive drab'        (142 142 56)
+	    'sgi salmon'    (198 113 113)
+	    'sgi slate blue'        (113 113 198)
+	    'sgi teal'      (56 142 142)
+	    'sgi very dark gray'    (40 40 40)
+	    'sgi very dark grey'    (40 40 40)
+	    'sgi very light gray'   (214 214 214)
+	    'sgi very light grey'   (214 214 214)
+	    'SGIBeet'       (142 56 142)
+	    'SGIBrightGray' (197 193 170)
+	    'SGIBrightGrey' (197 193 170)
+	    'SGIChartreuse' (113 198 113)
+	    'SGIDarkGray'   (85 85 85)
+	    'SGIDarkGrey'   (85 85 85)
+	    'SGIGray0'      (0 0 0)
+	    'SGIGray100'    (255 255 255)
+	    'SGIGray12'     (30 30 30)
+	    'SGIGray16'     (40 40 40)
+	    'SGIGray20'     (51 51 51)
+	    'SGIGray24'     (61 61 61)
+	    'SGIGray28'     (71 71 71)
+	    'SGIGray32'     (81 81 81)
+	    'SGIGray36'     (91 91 91)
+	    'SGIGray4'      (10 10 10)
+	    'SGIGray40'     (102 102 102)
+	    'SGIGray44'     (112 112 112)
+	    'SGIGray48'     (122 122 122)
+	    'SGIGray52'     (132 132 132)
+	    'SGIGray56'     (142 142 142)
+	    'SGIGray60'     (153 153 153)
+	    'SGIGray64'     (163 163 163)
+	    'SGIGray68'     (173 173 173)
+	    'SGIGray72'     (183 183 183)
+	    'SGIGray76'     (193 193 193)
+	    'SGIGray8'      (20 20 20)
+	    'SGIGray80'     (204 204 204)
+	    'SGIGray84'     (214 214 214)
+	    'SGIGray88'     (224 224 224)
+	    'SGIGray92'     (234 234 234)
+	    'SGIGray96'     (244 244 244)
+	    'SGIGrey0'      (0 0 0)
+	    'SGIGrey100'    (255 255 255)
+	    'SGIGrey12'     (30 30 30)
+	    'SGIGrey16'     (40 40 40)
+	    'SGIGrey20'     (51 51 51)
+	    'SGIGrey24'     (61 61 61)
+	    'SGIGrey28'     (71 71 71)
+	    'SGIGrey32'     (81 81 81)
+	    'SGIGrey36'     (91 91 91)
+	    'SGIGrey4'      (10 10 10)
+	    'SGIGrey40'     (102 102 102)
+	    'SGIGrey44'     (112 112 112)
+	    'SGIGrey48'     (122 122 122)
+	    'SGIGrey52'     (132 132 132)
+	    'SGIGrey56'     (142 142 142)
+	    'SGIGrey60'     (153 153 153)
+	    'SGIGrey64'     (163 163 163)
+	    'SGIGrey68'     (173 173 173)
+	    'SGIGrey72'     (183 183 183)
+	    'SGIGrey76'     (193 193 193)
+	    'SGIGrey8'      (20 20 20)
+	    'SGIGrey80'     (204 204 204)
+	    'SGIGrey84'     (214 214 214)
+	    'SGIGrey88'     (224 224 224)
+	    'SGIGrey92'     (234 234 234)
+	    'SGIGrey96'     (244 244 244)
+	    'SGILightBlue'  (125 158 192)
+	    'SGILightGray'  (170 170 170)
+	    'SGILightGrey'  (170 170 170)
+	    'SGIMediumGray' (132 132 132)
+	    'SGIMediumGrey' (132 132 132)
+	    'SGIOliveDrab'  (142 142 56)
+	    'SGISalmon'     (198 113 113)
+	    'SGISlateBlue'  (113 113 198)
+	    'SGITeal'       (56 142 142)
+	    'SGIVeryDarkGray'       (40 40 40)
+	    'SGIVeryDarkGrey'       (40 40 40)
+	    'SGIVeryLightGray'      (214 214 214)
+	    'SGIVeryLightGrey'      (214 214 214)
+	    'sienna'        (160 82 45)
+	    'sienna1'       (255 130 71)
+	    'sienna2'       (238 121 66)
+	    'sienna3'       (205 104 57)
+	    'sienna4'       (139 71 38)
+	    'skyblue'       (135 206 235)
+	    'SkyBlue1'      (135 206 255)
+	    'SkyBlue2'      (126 192 238)
+	    'SkyBlue3'      (108 166 205)
+	    'SkyBlue4'      (74 112 139)
+	    'slategray'     (112 128 144)
+	    'slategrey'     (112 128 144)
+	    'slateblue'     (106 90 205)
+	    'SlateBlue1'    (131 111 255)
+	    'SlateBlue2'    (122 103 238)
+	    'SlateBlue3'    (105 89 205)
+	    'SlateBlue4'    (71 60 139)
+	    'SlateGray1'    (198 226 255)
+	    'SlateGray2'    (185 211 238)
+	    'SlateGray3'    (159 182 205)
+	    'SlateGray4'    (108 123 139)
+	    'snow'          (255 250 250)
+	    'snow1'         (255 250 250)
+	    'snow2'         (238 233 233)
+	    'snow3'         (205 201 201)
+	    'snow4'         (139 137 137)
+	    'springgreen'   (0 255 127)
+	    'SpringGreen1'  (0 255 127)
+	    'SpringGreen2'  (0 238 118)
+	    'SpringGreen3'  (0 205 102)
+	    'SpringGreen4'  (0 139 69)
+	    'steelblue'     (70 130 180)
+	    'SteelBlue1'    (99 184 255)
+	    'SteelBlue2'    (92 172 238)
+	    'SteelBlue3'    (79 148 205)
+	    'SteelBlue4'    (54 100 139)
+	    'tan'   (210 180 140)
+	    'tan1'  (255 165 79)
+	    'tan2'  (238 154 73)
+	    'tan3'  (205 133 63)
+	    'tan4'  (139 90 43)
+	    'thistle'       (216 191 216)
+	    'thistle1'      (255 225 255)
+	    'thistle2'      (238 210 238)
+	    'thistle3'      (205 181 205)
+	    'thistle4'      (139 123 139)
+	    'tomato'        (255 99 71)
+	    'tomato1'       (255 99 71)
+	    'tomato2'       (238 92 66)
+	    'tomato3'       (205 79 57)
+	    'tomato4'       (139 54 38)
+	    'turquoise'     (64 224 208)
+	    'turquoise1'    (0 245 255)
+	    'turquoise2'    (0 229 238)
+	    'turquoise3'    (0 197 205)
+	    'turquoise4'    (0 134 139)
+	    'violet'        (238 130 238)
+	    'violetred'     (208 32 144)
+	    'VioletRed1'    (255 62 150)
+	    'VioletRed2'    (238 58 140)
+	    'VioletRed3'    (205 50 120)
+	    'VioletRed4'    (139 34 82)
+	    'wheat'         (245 222 179)
+	    'wheat1'        (255 231 186)
+	    'wheat2'        (238 216 174)
+	    'wheat3'        (205 186 150)
+	    'wheat4'        (139 126 102)
+	    'white'         (255 255 255)
+	    'whitesmoke'    (245 245 245)
+	    'yellow'        (255 255 0)
+	    'yellowgreen'   (154 205 50)
+	    'yellow1'       (255 255 0)
+	    'yellow2'       (238 238 0)
+	    'yellow3'       (205 205 0)
+	    'yellow4'       (139 139 0)
+	).
+
     "
      WinWorkstation initializeStandardColorNames
     "
@@ -6294,130 +6256,130 @@
 
     msg = 'WM_ALL' ifTrue:[
 %{
-	__debug_WM_ALL__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_ALL__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_USER' ifTrue:[
 %{
-	__debug_WM_MOUSEENTER__ = (aBoolean == true) ? 1 : 0;
-	__debug_WM_MOUSELEAVE__ = (aBoolean == true) ? 1 : 0;
-	__debug_WM_MOUSEMOVE__ = (aBoolean == true) ? 1 : 0;
-	__debug_WM_MOUSEACTIVATE__ = (aBoolean == true) ? 1 : 0;
-	__debug_WM_BUTTONUP__ = (aBoolean == true) ? 1 : 0;
-	__debug_WM_BUTTONDOWN__ = (aBoolean == true) ? 1 : 0;
-	__debug_WM_KEYUP__ = (aBoolean == true) ? 1 : 0;
-	__debug_WM_KEYDOWN__ = (aBoolean == true) ? 1 : 0;
-	__debug_WM_CHAR__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_MOUSEENTER__ = (aBoolean == true);
+	__debug_WM_MOUSELEAVE__ = (aBoolean == true);
+	__debug_WM_MOUSEMOVE__ = (aBoolean == true);
+	__debug_WM_MOUSEACTIVATE__ = (aBoolean == true);
+	__debug_WM_BUTTONUP__ = (aBoolean == true);
+	__debug_WM_BUTTONDOWN__ = (aBoolean == true);
+	__debug_WM_KEYUP__ = (aBoolean == true);
+	__debug_WM_KEYDOWN__ = (aBoolean == true);
+	__debug_WM_CHAR__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
 
     msg = 'WM_MOUSEENTER' ifTrue:[
 %{
-	__debug_WM_MOUSEENTER__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_MOUSEENTER__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_MOUSELEAVE' ifTrue:[
 %{
-	__debug_WM_MOUSELEAVE__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_MOUSELEAVE__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_MOUSEMOVE' ifTrue:[
 %{
-	__debug_WM_MOUSEMOVE__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_MOUSEMOVE__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_MOUSEACTIVATE' ifTrue:[
 %{
-	__debug_WM_MOUSEACTIVATE__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_MOUSEACTIVATE__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_BUTTONUP' ifTrue:[
 %{
-	__debug_WM_BUTTONUP__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_BUTTONUP__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_BUTTONDOWN' ifTrue:[
 %{
-	__debug_WM_BUTTONDOWN__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_BUTTONDOWN__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_KEYUP' ifTrue:[
 %{
-	__debug_WM_KEYUP__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_KEYUP__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_KEYDOWN' ifTrue:[
 %{
-	__debug_WM_KEYDOWN__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_KEYDOWN__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_CHAR' ifTrue:[
 %{
-	__debug_WM_CHAR__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_CHAR__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_PAINT' ifTrue:[
 %{
-	__debug_WM_PAINT__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_PAINT__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_MOVING' ifTrue:[
 %{
-	__debug_WM_MOVING__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_MOVING__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_ERASEBKGND' ifTrue:[
 %{
-	__debug_WM_ERASEBKGND__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_ERASEBKGND__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_SETTEXT' ifTrue:[
 %{
-	__debug_WM_SETTEXT__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_SETTEXT__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_COPYDATA' ifTrue:[
 %{
-	__debug_WM_COPYDATA__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_COPYDATA__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_DROPFILES' ifTrue:[
 %{
-	__debug_WM_DROPFILES__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_DROPFILES__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_SHOWWINDOW' ifTrue:[
 %{
-	__debug_WM_SHOWWINDOW__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_SHOWWINDOW__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_SETCURSOR' ifTrue:[
 %{
-	__debug_WM_SETCURSOR__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_SETCURSOR__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
     msg = 'WM_FOCUS' ifTrue:[
 %{
-	__debug_WM_FOCUS__ = (aBoolean == true) ? 1 : 0;
+	__debug_WM_FOCUS__ = (aBoolean == true);
 	RETURN (self);
 %}
     ].
@@ -6434,7 +6396,7 @@
      WinWorkstation debug:true message:'WM_KEYUP'
      WinWorkstation debug:true message:'WM_KEYDOWN'
      WinWorkstation debug:true message:'WM_CHAR'
-     WinWorkstation debug:true message:'WM_BUTTONDOWN'
+     WinWorkstation debug:true message:'WM_COPYDATA'
     "
 !
 
@@ -6451,7 +6413,7 @@
 debugNative:aBoolean
 %{  /* NOCONTEXT */
 
-    __debugNative__ = (aBoolean == true) ? 1 : 0;
+    __debugNative__ = (aBoolean == true);
 %}
     "
      WinWorkstation debugNative:true
@@ -9703,44 +9665,49 @@
 getScaledRGBFromName:colorName into:aBlock
     "get scaled rgb components (0..16rFFFF) of color named colorName,
      and evaluate the 3-arg block, aBlock with them.
-     Return nil for unknown color names."
+     Return nil for unknown color names or invalid hex numbers."
 
     |triple r g b found cName|
 
     r := g := b := 0.
     found := false.
     (colorName startsWith:$#) ifTrue:[
-	"/ color in r/g/b hex notation
-	r := Integer readFrom:(colorName copyFrom:2 to:3) radix:16.
-	g := Integer readFrom:(colorName copyFrom:4 to:5) radix:16.
-	b := Integer readFrom:(colorName copyFrom:6 to:7) radix:16.
-	found := true.
+        "/ color in r/g/b hex notation
+        colorName size == 7 ifTrue:[
+            r := Integer readFrom:(colorName copyFrom:2 to:3) radix:16 onError:[nil].
+            g := Integer readFrom:(colorName copyFrom:4 to:5) radix:16 onError:[nil].
+            b := Integer readFrom:(colorName copyFrom:6 to:7) radix:16 onError:[nil].
+        ].
+        (r isNil or:[g isNil or:[b isNil]]) ifTrue:[^ nil].
+        found := true.
     ] ifFalse:[
-	cName := colorName asString.
-	triple := StandardColorValues at:cName ifAbsent:nil.
-	triple isNil ifTrue:[
-	    "/ try lowercase name
-	    cName := cName asLowercase.
-	    triple := StandardColorValues at:cName ifAbsent:nil.
-	    triple isNil ifTrue:[
-		"/ try lowercase without intermixed spaces
-		cName := cName asCollectionOfWords asStringWith:nil.
-		triple := StandardColorValues at:cName ifAbsent:nil.
-	    ].
-	].
-	triple notNil ifTrue:[
-	    r := triple at:1.
-	    g := triple at:2.
-	    b := triple at:3.
-	    found := true.
-	].
+        cName := colorName asString.
+        triple := StandardColorValues at:cName ifAbsent:nil.
+        triple isNil ifTrue:[
+            "/ try lowercase name
+            cName := cName asLowercase.
+            triple := StandardColorValues at:cName ifAbsent:nil.
+            triple isNil ifTrue:[
+                "/ try lowercase without intermixed spaces
+                cName := cName asCollectionOfWords asStringWith:nil.
+                triple := StandardColorValues at:cName ifAbsent:nil.
+            ].
+        ].
+        triple notNil ifTrue:[
+            r := triple at:1.
+            g := triple at:2.
+            b := triple at:3.
+            found := true.
+        ].
     ].
     found ifFalse:[
-	"/ ('WinWorkstation: unknown color: ' , colorName) infoPrintCR.
-	^ nil.
+        "/ ('WinWorkstation: unknown color: ' , colorName) infoPrintCR.
+        ^ nil.
     ].
 
     ^ aBlock value:((r * 256) + r) value:((g * 256) + g) value:((b * 256) + b)
+
+    "Modified (comment): / 14-11-2016 / 14:02:11 / cg"
 !
 
 listOfAvailableColors
@@ -12738,14 +12705,15 @@
 
 	    /* message from another process */
 	    case WM_COPYDATA:
-		DPRINTF((">>> WM_COPYDATA\n"));
+		DPRINTF((">>> WM_COPYDATA"));
 		{
 		    OBJ eventData;
 		    void *data = (void *)(ev->ev_arg1);
-		    int nBytes = ev->ev_arg2;
-
-		    if (ev->ev_arg1) {
-			eventData = __MKBYTEARRAY(data, nBytes);
+		    DPRINTFIF((__debug_WM_COPYDATA__) , (">>> WM_COPYDATA %s (%d)\n", data, ev->ev_arg2));
+
+		    if (data) {
+			eventData = __MKBYTEARRAY(data, (int)ev->ev_arg2);
+			free(data);     // see winEventProcessing()
 		    } else {
 			eventData = nil;
 		    }
@@ -13736,9 +13704,9 @@
 %{
     if (__tmpDC) {
 #ifdef USE_EnumFontFamiliesEx
-	EnumFontFamiliesEx( __tmpDC, NULL, EnumFPTypeFaceProc, (INT)&(typeFaceList));
-#else
-	EnumFontFamilies( __tmpDC, NULL, EnumFPTypeFaceProc, (INT)&(typeFaceList));
+	EnumFontFamiliesEx( __tmpDC, NULL, EnumFPTypeFaceProc, (INT)&typeFaceList);
+#else
+	EnumFontFamilies( __tmpDC, NULL, EnumFPTypeFaceProc, (INT)&typeFaceList);
 #endif
     }
 %}
@@ -13751,9 +13719,9 @@
     if (__isStringLike(typeFace)) {
 	if (__tmpDC) {
 #ifdef USE_EnumFontFamiliesEx
-	    EnumFontFamiliesEx(__tmpDC, __stringVal(typeFace), EnumFontsProc, (INT)&(fontList));
-#else
-	    EnumFontFamilies(__tmpDC, __stringVal(typeFace), EnumFontsProc, (INT)&(fontList));
+	    EnumFontFamiliesEx(__tmpDC, __stringVal(typeFace), EnumFontsProc, (INT)&fontList);
+#else
+	    EnumFontFamilies(__tmpDC, __stringVal(typeFace), EnumFontsProc, (INT)&fontList);
 #endif
 	}
     }
@@ -15596,7 +15564,7 @@
 
     data.hArray = handleArray;
     data.index = 0;
-    EnumDisplayMonitors(NULL, NULL, EnumDisplayMonitorsProc, (INT)(&data));
+    EnumDisplayMonitors(NULL, NULL, EnumDisplayMonitorsProc, (INT)&data);
 %}.
     ^ handleArray
 
@@ -17756,13 +17724,13 @@
 
     ((lpClassName notNil and:[lpClassName isWideString])
      or:[lpWindowName notNil and:[lpWindowName isWideString]]) ifTrue:[
-        ^ self
-            primFindWindowW:(lpClassName isNil
-                                    ifTrue:[nil]
-                                    ifFalse:[lpClassName asUnicode16StringZ])
-            windowName:(lpWindowName isNil
-                                    ifTrue:[nil]
-                                    ifFalse:[lpWindowName asUnicode16StringZ])
+	^ self
+	    primFindWindowW:(lpClassName isNil
+				    ifTrue:[nil]
+				    ifFalse:[lpClassName asUnicode16StringZ])
+	    windowName:(lpWindowName isNil
+				    ifTrue:[nil]
+				    ifFalse:[lpWindowName asUnicode16StringZ])
     ].
     ^ self primFindWindowA:lpClassName windowName:lpWindowName
 
@@ -18275,7 +18243,7 @@
     <apicall: handle "FindWindowW" (pointer pointer) module: "user32.dll" >
 
     "
-     Display primFindWindowW: nil windowName: 'ST/X Launcher' asUnicode16String 
+     Display primFindWindowW: nil windowName: 'ST/X Launcher' asUnicode16String
     "
 !
 
@@ -18646,9 +18614,9 @@
 
     externalBytes := aByteArrayOrString asExternalBytesUnprotected.
     copyDataStruct := CopyDataStructStructure new.
-    copyDataStruct 
-        cbData:externalBytes size;
-        lpData:externalBytes address.
+    copyDataStruct
+	cbData:externalBytes size;
+	lpData:externalBytes address.
     lParam := copyDataStruct asExternalBytesUnprotected.
     ^ self primSendMessage:aWindowId message:messageType wParam:nil lParam:lParam.
 
@@ -19392,7 +19360,7 @@
 
 sizeInBytes
     ExternalAddress pointerSize == 8 ifTrue:[
-        ^ 20.
+	^ 24.
     ].
     ^ 12
 ! !
@@ -19408,46 +19376,46 @@
 
 cbData
     ExternalAddress pointerSize == 8 ifTrue:[
-        ^ self unsignedInt32At: 8 + 1.
+	^ self unsignedInt32At: 8 + 1.
     ].
     ^ self unsignedInt32At: 4 + 1.
 !
 
 cbData: cbData
     ExternalAddress pointerSize == 8 ifTrue:[
-        self unsignedInt32At: 8 + 1  put: cbData.
+	self unsignedInt32At: 8 + 1  put: cbData.
     ] ifFalse:[
-        self unsignedInt32At: 4 + 1  put: cbData.
+	self unsignedInt32At: 4 + 1  put: cbData.
     ].
 !
 
 dwData
     ExternalAddress pointerSize == 8 ifTrue:[
-        ^ self unsignedInt64At: 0 + 1.
+	^ self unsignedInt64At: 0 + 1.
     ].
     ^ self unsignedInt32At: 0 + 1.
 !
 
 dwData: dwData
     ExternalAddress pointerSize == 8 ifTrue:[
-        self unsignedInt64At: 0 + 1 put:dwData.
+	self unsignedInt64At: 0 + 1 put:dwData.
     ] ifFalse:[
-        self unsignedInt32At: 0 + 1 put:dwData.
+	self unsignedInt32At: 0 + 1 put:dwData.
     ].
 !
 
 lpData
     ExternalAddress pointerSize == 8 ifTrue:[
-        ^ self unsignedInt64At: 12 + 1.
+	^ self unsignedInt64At: 16 + 1.
     ].
     ^ self unsignedInt32At: 8 + 1.
 !
 
 lpData: lpData
     ExternalAddress pointerSize == 8 ifTrue:[
-        self unsignedInt64At: 12 + 1  put: lpData.
+	self unsignedInt64At: 16 + 1  put: lpData.
     ] ifFalse:[
-        self unsignedInt32At: 8 + 1  put: lpData.
+	self unsignedInt32At: 8 + 1  put: lpData.
     ].
 ! !
 
--- a/WindowGroup.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/WindowGroup.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -19,7 +21,8 @@
 		pointerView isForModalSubview focusByTab groupHasFocus busyHook
 		busyHookTimeout inModalLoop isDebugged preEventHooks
 		postEventHooks creatingProcess traceEvents processPriority
-		inWithCursorDoBlock doNotCloseOnAbortSignal previousFocusView'
+		inWithCursorDoBlock doNotCloseOnAbortSignal previousFocusView
+		modalGroup'
 	classVariableNames:'LastActiveGroup LastActiveProcess LeaveSignal
 		WindowGroupQuerySignal LastEventQuerySignal BusyHookTime'
 	poolDictionaries:''
@@ -141,8 +144,8 @@
       a busy cursor (hour-glass) in an application, if some processing takes some time
       (without a need for #withCursorDo: all over the place in the application)
 
-    Dont get confused:
-        You dont have to care for all those details in the normal case;
+    Don't get confused:
+        You don't have to care for all those details in the normal case;
         a windowgroup is created for you automatically, when a view is opened.
         All of the internals are not required to be known for most applications.
 
@@ -159,16 +162,20 @@
 
         isModal                 true if this is for a modal box; i.e. running a separate
                                 modal event loop on top of another window group.
-                                Those execute in the same process as the underlying group
+                                Those modal groups execute in the same process as the underlying group
 
         inModalLoop             true if this group's event processing is currently suspended
                                 because I have opened a modal window (with its own 'isModal'
                                 group) which handles events for a while.
 
+        modalGroup              non-nil windowGroup which is my modal windowGroup, if I am
+                                in a modal loop. I.e. the group which has been started by me and
+                                which has taken control.
+
+        previousGroup           if modal, the group that started this one (might be another modal one)
+
         isDebugged              true if a debugger sits on top of me
 
-        previousGroup           if modal, the group that started this one
-
         focusView               the one that has the keyboard focus (or nil)
 
         focusByTab              if focus came via tabbing 
@@ -394,6 +401,10 @@
 
 !
 
+flushCachedActiveGroup
+    self setActiveGroup:nil
+!
+
 scheduledWindowGroups
     "return a collection of all windowGroups (possibly for different
      display devices) which are scheduled 
@@ -412,7 +423,7 @@
             |wg|
 
             (wg := aView windowGroup) notNil ifTrue:[
-                wg process notNil ifTrue:[
+                (wg process notNil and:[wg process isDead not]) ifTrue:[
                     (set includes:wg) ifFalse:[
                         set add:wg.
                         coll add:wg.
@@ -582,7 +593,10 @@
     "return true, if the receiver has given up control to some other modal windowGroup
      (i.e. if it has popped up a modal dialog or a popUpMenu)"
 
+    "/ ^ modalGroup notNil.
     ^ inModalLoop ? false
+
+    "Modified: / 13-11-2016 / 22:59:29 / cg"
 !
 
 isModal
@@ -608,6 +622,7 @@
     g := self.
     [(g isModal or:[g isPopUp])
      and:[(prev := g previousGroup) notNil]] whileTrue:[
+        g == prev ifTrue:[^ g]. 
         g := prev
     ].
     ^ g
@@ -627,6 +642,15 @@
     "Created: 20.8.1997 / 17:57:35 / cg"
 !
 
+modalGroup
+    "if the receiver has given up control to some other modal windowGroup
+     (i.e. if it has popped up a modal dialog or a popUpMenu), this is the modelGroup"
+
+    ^ modalGroup
+
+    "Modified (comment): / 15-11-2016 / 00:13:47 / cg"
+!
+
 previousGroup
     "return the windowgroup that started this group. (for modal groups only).
      This may be another modalGroup (for boxes opened by boxes).
@@ -957,13 +981,20 @@
     "invoked, when a modal dialog is closed"
 
     inModalLoop := false.
+    modalGroup := nil.
+
+    "Modified: / 13-11-2016 / 22:59:11 / cg"
 !
 
-modalDialogStarts
+modalDialogStarts:aModalGroup
     "invoked, when a modal dialog is opened"
 
     self processEvents. "/ process any bufferd message send events
     inModalLoop := true.
+    modalGroup := aModalGroup.
+
+    "Created: / 13-11-2016 / 17:18:31 / cg"
+    "Modified: / 13-11-2016 / 22:58:57 / cg"
 !
 
 realizeTopViews
@@ -1063,8 +1094,9 @@
     "set previousGroup to the main (non-modal) group"
 
     previousGroup isNil ifTrue:[
-        self assert:(mainGroup ~~ self).
-        previousGroup := mainGroup
+        (mainGroup ~~ self) ifTrue:[
+            previousGroup := mainGroup
+        ].
     ].
     prevGroup := previousGroup.
     prevGroup notNil ifTrue:[
@@ -1088,17 +1120,11 @@
 
     mainGroup notNil ifTrue:[
         "/ tell the other group, that some modal dialog has started.
-        mainGroup modalDialogStarts
+        mainGroup modalDialogStarts:self.
     ].
     [
-        WindowGroupQuerySignal answer:self do:[
-            LastActiveGroup := nil.
-
-            self realizeTopViews.
-            self 
-                eventLoopWhile:checkBlock 
-                onLeave:[]
-        ].
+        self realizeTopViews.
+        self eventLoopWhile:checkBlock onLeave:[]
     ] ensure:[
         mainGroup notNil ifTrue:[
             "/ tell the other group, that some modal dialog has closed down.
@@ -1135,8 +1161,9 @@
     prevActivePointerGrab notNil ifTrue:[ device grabPointerInView:prevActivePointerGrab ].
     prevActiveKeyboardGrab notNil ifTrue:[ device grabKeyboardInView:prevActiveKeyboardGrab ].
 
-    "Created: 10.12.1995 / 14:14:26 / cg"
-    "Modified: 20.8.1997 / 18:12:20 / cg"
+    "Created: / 10-12-1995 / 14:14:26 / cg"
+    "Modified: / 13-11-2016 / 17:19:16 / cg"
+    "Modified (format): / 14-11-2016 / 10:24:03 / cg"
 !
 
 startupWith:startupAction
@@ -1161,28 +1188,25 @@
         "/ (well, not really forever ... ;-)
 
         myProcess := [
-            WindowGroupQuerySignal answer:self do:[
-                LastActiveGroup := nil.
-                [
-                    startupAction value.
-                    self showWaitCursorWhenBusyForMillis:400.
-                    self eventLoopWhile:[true] onLeave:[]
-                ] ensure:[
-                    |dev w app|
-
-                    (w := self mainView) notNil ifTrue:[
-                        (app := w application) notNil ifTrue:[
-                            app release
-                        ]
-                    ].
-                    (dev := self graphicsDevice) notNil ifTrue:[
-                        dev deviceIOErrorSignal handle:[:ex |
-                        ] do:[
-                            "/ just in case the view did not yet have a chance to 
-                            "/ shutDown properly (process killed in processMonitor)
-                            views notNil ifTrue:[
-                                self closeDownViews
-                            ]
+            [
+                startupAction value.
+                self showWaitCursorWhenBusyForMillis:400.
+                self eventLoopWhile:[true] onLeave:[]
+            ] ensure:[
+                |dev w app|
+
+                (w := self mainView) notNil ifTrue:[
+                    (app := w application) notNil ifTrue:[
+                        app release
+                    ]
+                ].
+                (dev := self graphicsDevice) notNil ifTrue:[
+                    dev deviceIOErrorSignal handle:[:ex |
+                    ] do:[
+                        "/ just in case the view did not yet have a chance to 
+                        "/ shutDown properly (process killed in processMonitor)
+                        views notNil ifTrue:[
+                            self closeDownViews
                         ]
                     ]
                 ]
@@ -1364,174 +1388,171 @@
         signalsToHandle add:AbortOperationRequest
     ].
 
-    [
-        |p g s mainGroup mySema waitSema mainSema groupForSema|
-
-        waitSema := mySema := mySensor eventSemaphore.
-
-        isModal ifTrue:[
-            mainGroup := self mainGroup.
-            mainGroup == self ifTrue:[
-                mainGroup := nil
-            ].
-        ] ifFalse:[
-            mainGroup := previousGroup
-        ].
-
-        "/ if this is an event loop for a modal loop (popup or dialog),
-        "/ also make sure that we react on events coming for the mainGroup
-        "/ to allow for redraw of those views.
-        mainGroup notNil ifTrue:[
-            mainSema := mainGroup sensor eventSemaphore.
-            waitSema := SemaphoreSet with:mySema with:mainSema.
-
-            "/ must also care for all other groups in between
-            "/ (in case its a modal dialog opened from a modal dialog)
-            g := previousGroup.
-            g ~~ mainGroup ifTrue:[
-                groupForSema := IdentityDictionary new.
-                [g ~~ mainGroup] whileTrue:[
-                    g sensor notNil ifTrue:[
-                        s := g sensor eventSemaphore.
-                        waitSema add:s.
-                        groupForSema at:s put:g.
-                    ].
-                    g := g previousGroup.
-                ]
+    WindowGroupQuerySignal answer:self do:[
+        [
+            |p g s mainGroup mySema waitSema mainSema groupForSema|
+
+            waitSema := mySema := mySensor eventSemaphore.
+
+            isModal ifTrue:[
+                mainGroup := self mainGroup.
+                mainGroup == self ifTrue:[
+                    mainGroup := nil
+                ].
+            ] ifFalse:[
+                mainGroup := previousGroup
             ].
-        ].
-
-        [aBlock value] whileTrue:[ 
-            LastActiveGroup := self.
-            LastActiveProcess := thisProcess.
-
-            (views isNil and:[topViews isNil]) ifTrue:[
-                myProcess notNil ifTrue:[
-                    self shutDownProcess.
-                    "not reached - there is no life after death"
+
+            "/ if this is an event loop for a modal loop (popup or dialog),
+            "/ also make sure that we react on events coming for the mainGroup
+            "/ to allow for redraw of those views.
+            mainGroup notNil ifTrue:[
+                mainSema := mainGroup sensor eventSemaphore.
+                waitSema := SemaphoreSet with:mySema with:mainSema.
+
+                "/ must also care for all other groups in between
+                "/ (in case its a modal dialog opened from a modal dialog)
+                g := previousGroup.
+                g ~~ mainGroup ifTrue:[
+                    groupForSema := IdentityDictionary new.
+                    [g ~~ mainGroup] whileTrue:[
+                        g sensor notNil ifTrue:[
+                            s := g sensor eventSemaphore.
+                            waitSema add:s.
+                            groupForSema at:s put:g.
+                        ].
+                        g := g previousGroup.
+                    ]
                 ].
-                "
-                 this is the end of a modal loop
-                 (not having a private process ...)
-                "
-                ^ self
             ].
 
-            (graphicsDevice notNil and:[graphicsDevice isOpen not]) ifTrue:[
-                self closeDownViews.
-                ^ self.
-            ].
-
-            signalsToHandle handle:[:ex |
-                |theSig|
-
-                theSig := ex creator.
-                (AbortAllOperationRequest accepts:theSig) ifTrue:[
-                    "on AbortAllOperationRequest or AbortOperationRequest, 
-                     stay in loop"
-                    ex return
-                ].
-                theSig == LeaveSignal ifTrue:[
-                    "/
-                    "/ on leave, exit the event loop
-                    "/
-                    self closeDownViews.    
+            [aBlock value] whileTrue:[ 
+                (views isNil and:[topViews isNil]) ifTrue:[
+                    myProcess notNil ifTrue:[
+                        self shutDownProcess.
+                        "not reached - there is no life after death"
+                    ].
+                    "
+                     this is the end of a modal loop
+                     (not having a private process ...)
+                    "
                     ^ self
                 ].
 
-                "/ ActivityNotification
-                "/
-                "/ if I am a modal-group, let it be handled
-                "/ by the outer main-groups handler (but only if there is one)
-                "/ otherwise show the activityMessage and continue.
-                "/
-                isModal ifTrue:[
-                    (theSig isHandledIn:ex handlerContext sender) ifTrue:[
-                        ex reject.
-                        "never reached"
-                    ].
-                ] ifFalse:[
-                    self showActivity:ex messageText.
+                (graphicsDevice notNil and:[graphicsDevice isOpen not]) ifTrue:[
+                    self closeDownViews.
+                    ^ self.
                 ].
-                ex proceedWith:nil.
-            ] do:[
-                |dev gotSema mainView|
-
-                (mainGroup notNil or:[mySensor hasEvents not]) ifTrue:[
-                    waitSema isNil ifTrue:[
-                        "/ oops - how can this happen ....
-                        ^ self.
+
+                signalsToHandle handle:[:ex |
+                    |theSig|
+
+                    theSig := ex creator.
+                    (AbortAllOperationRequest accepts:theSig) ifTrue:[
+                        "on AbortAllOperationRequest or AbortOperationRequest, 
+                         stay in loop"
+                        ex return
                     ].
-                    "/ Flush device output before going to sleep. 
-                    "/ This may produce more events to arrive.
-                    "/ Q: is this still needed (see suspendAction) ?
-                    Error 
-                        handle:[:ex |
-                            (graphicsDevice notNil and:[graphicsDevice isOpen not]) ifTrue:[
-                                'WindowGroup [warning]: Error in flush - closing views' errorPrintCR.
-                                self closeDownViews.
-                                ^ self.
-                            ].
+                    theSig == LeaveSignal ifTrue:[
+                        "/
+                        "/ on leave, exit the event loop
+                        "/
+                        self closeDownViews.    
+                        ^ self
+                    ].
+
+                    "/ ActivityNotification
+                    "/
+                    "/ if I am a modal-group, let it be handled
+                    "/ by the outer main-groups handler (but only if there is one)
+                    "/ otherwise show the activityMessage and continue.
+                    "/
+                    isModal ifTrue:[
+                        (theSig isHandledIn:ex handlerContext sender) ifTrue:[
                             ex reject.
-                        ] 
-                        do:[
-                            self graphicsDevice flush.
+                            "never reached"
                         ].
-
-                    self isModal ifTrue:[
-                        thisProcess setStateTo:#modalEventWait if:#active.
                     ] ifFalse:[
-                        thisProcess setStateTo:#eventWait if:#active.
+                        self showActivity:ex messageText.
                     ].
-
-                    "/ now, wait for an event to arrive
-                    gotSema := waitSema wait.
-                ] ifFalse:[
-                    gotSema := mySema
-                ].
-                LastActiveGroup := self.
-                LastActiveProcess := thisProcess.
-
-                "/ some bad guy ;-) could have closed all down
-                "/ in the meanwhile ...
-                mySensor notNil ifTrue:[
-                    gotSema == mySema ifTrue:[
-                        "/
-                        "/ an event for me 
-                        "/
-                        self processEventsWithModalGroup:nil
+                    ex proceedWith:nil.
+                ] do:[
+                    |dev gotSema mainView|
+
+                    (mainGroup notNil or:[mySensor hasEvents not]) ifTrue:[
+                        waitSema isNil ifTrue:[
+                            "/ oops - how can this happen ....
+                            ^ self.
+                        ].
+                        "/ Flush device output before going to sleep. 
+                        "/ This may produce more events to arrive.
+                        "/ Q: is this still needed (see suspendAction) ?
+                        Error 
+                            handle:[:ex |
+                                (graphicsDevice notNil and:[graphicsDevice isOpen not]) ifTrue:[
+                                    'WindowGroup [warning]: Error in flush - closing views' errorPrintCR.
+                                    self closeDownViews.
+                                    ^ self.
+                                ].
+                                ex reject.
+                            ] 
+                            do:[
+                                self graphicsDevice flush.
+                            ].
+
+                        self isModal ifTrue:[
+                            thisProcess setStateTo:#modalEventWait if:#active.
+                        ] ifFalse:[
+                            thisProcess setStateTo:#eventWait if:#active.
+                        ].
+
+                        "/ now, wait for an event to arrive
+                        gotSema := waitSema wait.
                     ] ifFalse:[
-                        "/
-                        "/ modal and an event for my mainGroup or one of the groups in-between
-                        "/ (we arrive here after we woke up on maingroup sensor eventSemaphore)
-                        "/
-                        groupForSema notNil ifTrue:[
-                            g := groupForSema at:gotSema ifAbsent:nil.
-                            g := g ? mainGroup.
+                        gotSema := mySema
+                    ].
+
+                    "/ some bad guy ;-) could have closed all down
+                    "/ in the meanwhile ...
+                    mySensor notNil ifTrue:[
+                        gotSema == mySema ifTrue:[
+                            "/
+                            "/ an event for me 
+                            "/
+                            self processEventsWithModalGroup:nil
                         ] ifFalse:[
-                            g := mainGroup
-                        ].
-
-                        g topViews notNil ifTrue:[
-                            mainView := g topViews first
-                        ].
-                        mainView notNil ifTrue:[
-                            "/ if anything happened to the mainGroup
-                            "/ bring my own topView back to the front
-                            "/ This keeps modalBoxes visible
-                            "/ (not needed with X, where the windowManager does it for us)
-                            (g sensor hasConfigureEventFor:mainView) ifTrue:[
-                                (topViews size ~~ 0 and:[topViews first shown]) ifTrue:[
-                                    topViews first raiseDeiconified
+                            "/
+                            "/ modal and an event for my mainGroup or one of the groups in-between
+                            "/ (we arrive here after we woke up on maingroup sensor eventSemaphore)
+                            "/
+                            groupForSema notNil ifTrue:[
+                                g := groupForSema at:gotSema ifAbsent:nil.
+                                g := g ? mainGroup.
+                            ] ifFalse:[
+                                g := mainGroup
+                            ].
+
+                            g topViews notNil ifTrue:[
+                                mainView := g topViews first
+                            ].
+                            mainView notNil ifTrue:[
+                                "/ if anything happened to the mainGroup
+                                "/ bring my own topView back to the front
+                                "/ This keeps modalBoxes visible
+                                "/ (not needed with X, where the windowManager does it for us)
+                                (g sensor hasConfigureEventFor:mainView) ifTrue:[
+                                    (topViews size ~~ 0 and:[topViews first shown]) ifTrue:[
+                                        topViews first raiseDeiconified
+                                    ].
                                 ].
                             ].
-                        ].
-                        g processEventsWithModalGroup:self.
+                            g processEventsWithModalGroup:self.
+                        ]
                     ]
-                ]
+                ].
             ].
-        ].
-    ] ensure:cleanupActions
+        ] ensure:cleanupActions
+    ]
 
     "Modified: / 14-12-1995 / 11:12:24 / stefan"
     "Modified: / 06-07-2010 / 11:47:27 / cg"
@@ -1796,9 +1817,6 @@
                                 ].
                             ].
 
-                            LastActiveGroup := self.
-                            LastActiveProcess := Processor activeProcess.
-
                             (busyHook notNil and:[busyHookBlock isNil]) ifTrue:[
                                 (event isKeyEvent or:[event isButtonPressEvent]) ifTrue:[
                                     "/ start a timeout action - to invoke the busyHook after some time
@@ -1882,40 +1900,34 @@
     "process only pending expose events from the damage queue.
      This also handles resize, mapped and unmap events."
 
-    |event view sensor thisProcess|
+    |event view sensor|
 
     (sensor := mySensor) isNil ifTrue:[^ self].
     (sensor damageCount ~~ 0) ifTrue:[
-        thisProcess := Processor activeProcess.
-
-        [(event := sensor nextDamageEventFor:aViewOrNil) notNil] whileTrue:[
-            LastActiveGroup := self.
-            LastActiveProcess := thisProcess.
-
-            (views notNil or:[topViews notNil]) ifTrue:[
-                view := event view.
-                (aViewOrNil isNil or:[aViewOrNil == view]) ifTrue:[
-                    LastEventQuerySignal handle:[:ex |
-                        ex proceedWith:event
-                    ] do:[
-                        (self executePreEventHooksFor:event) ifFalse:[
-                            "/
-                            "/ if the view is no longer shown (iconified or closed),
-                            "/ this is a leftover event and ignored.
-                            "/
-                            "/ could this ever be a non-damage ?
-                            "/
-                            view notNil ifTrue:[
-                                (view shown or:[event isDamage not]) ifTrue:[
-                                    LastActiveGroup := self.
-                                    LastActiveProcess := thisProcess.
-
-                                    view dispatchEvent:event withFocusOn:nil delegate:true. 
+        WindowGroupQuerySignal answer:self do:[
+            [(event := sensor nextDamageEventFor:aViewOrNil) notNil] whileTrue:[
+                (views notNil or:[topViews notNil]) ifTrue:[
+                    view := event view.
+                    (aViewOrNil isNil or:[aViewOrNil == view]) ifTrue:[
+                        LastEventQuerySignal handle:[:ex |
+                            ex proceedWith:event
+                        ] do:[
+                            (self executePreEventHooksFor:event) ifFalse:[
+                                "/
+                                "/ if the view is no longer shown (iconified or closed),
+                                "/ this is a leftover event and ignored.
+                                "/
+                                "/ could this ever be a non-damage ?
+                                "/
+                                view notNil ifTrue:[
+                                    (view shown or:[event isDamage not]) ifTrue:[
+                                        view dispatchEvent:event withFocusOn:nil delegate:true. 
+                                    ].
                                 ].
                             ].
+                            self executePostEventHooksFor:event.
                         ].
-                        self executePostEventHooksFor:event.
-                    ].
+                    ]
                 ]
             ]
         ]
@@ -1949,31 +1961,28 @@
 
     thisProcess := Processor activeProcess.
 
-    [true] whileTrue:[
-        LastActiveGroup := self.
-        LastActiveProcess := thisProcess.
-
-        "/ event := aView nextDamage.
-        event := sensor nextExposeEventFor:someViewOrNil.
-        event isNil ifTrue:[^ self].
-
-        (views notNil or:[topViews notNil]) ifTrue:[
-            LastEventQuerySignal handle:[:ex |
-                ex proceedWith:event
-            ] do:[
-                (self executePreEventHooksFor:event) ifFalse:[
-                    view := event view.
-                    "/
-                    "/ if the view is no longer shown (iconified or closed),
-                    "/ this is a leftover event and ignored.
-                    "/
-                    view shown ifTrue:[
-                        LastActiveGroup := self.
-                        LastActiveProcess := thisProcess.
-                        view dispatchEvent:event withFocusOn:nil delegate:true. 
-                    ]
-                ].
-                self executePostEventHooksFor:event.
+    WindowGroupQuerySignal answer:self do:[
+        [true] whileTrue:[
+            "/ event := aView nextDamage.
+            event := sensor nextExposeEventFor:someViewOrNil.
+            event isNil ifTrue:[^ self].
+
+            (views notNil or:[topViews notNil]) ifTrue:[
+                LastEventQuerySignal handle:[:ex |
+                    ex proceedWith:event
+                ] do:[
+                    (self executePreEventHooksFor:event) ifFalse:[
+                        view := event view.
+                        "/
+                        "/ if the view is no longer shown (iconified or closed),
+                        "/ this is a leftover event and ignored.
+                        "/
+                        view shown ifTrue:[
+                            view dispatchEvent:event withFocusOn:nil delegate:true. 
+                        ]
+                    ].
+                    self executePostEventHooksFor:event.
+                ]
             ]
         ]
     ]
@@ -2675,21 +2684,25 @@
 !WindowGroup methodsFor:'special-accessing'!
 
 isForModalSubview 
-    "special for windowgroups for modal subviews.
+    "special for windowgroup with modal subviews.
      These must be flagged specially to avoid the views being reassigned
      to the maingroup.
      This is a private interface to the SimpleView class"
 
     ^ isForModalSubview
+
+    "Modified (comment): / 13-11-2016 / 17:09:18 / cg"
 !
 
 isForModalSubview:aBoolean
-    "special for windowgroups for modal subviews.
+    "special for windowgroups with modal subviews.
      These must be flagged specially to avoid the views being reassigned
      to the maingroup.
      This is a private interface to the SimpleView class"
 
     isForModalSubview := aBoolean
+
+    "Modified (comment): / 13-11-2016 / 17:09:22 / cg"
 !
 
 setModal:aBoolean
@@ -2889,6 +2902,20 @@
     "Created: / 27-07-2012 / 09:44:00 / cg"
 ! !
 
+!WindowGroup::WindowGroupQuery class methodsFor:'redefined answering'!
+
+answer:something do:action
+    |retVal|
+
+    [
+        WindowGroup flushCachedActiveGroup.
+        retVal := super answer:something do:action
+    ] ensure:[
+        WindowGroup flushCachedActiveGroup
+    ].
+    ^ retVal
+! !
+
 !WindowGroup class methodsFor:'documentation'!
 
 version
--- a/WindowSensor.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/WindowSensor.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
               All Rights Reserved
@@ -3109,7 +3107,7 @@
 
 altDown
     "return true, if the meta key is currently pressed.
-     Notice, that some keyboards dont have an alt key;
+     Notice, that some keyboards don't have an alt key;
      it is better to use 'sensor metaDown or:[sensor altDown]'."
 
     ^ altDown
@@ -3150,7 +3148,7 @@
 
 metaDown
     "return true, if the meta key is currently pressed.
-     Notice, that most keyboards dont have a meta key;
+     Notice, that most keyboards don't have a meta key;
      it is better to use 'sensor metaDown or:[sensor altDown]'."
 
     ^ metaDown
--- a/XWorkstation.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/XWorkstation.st	Fri Nov 18 21:26:33 2016 +0000
@@ -2910,7 +2910,7 @@
 
 colorNamed:aString
     "allocate a color with color name - return the color index (i.e. colorID).
-     Dont use this method, colornames are mostly X specific"
+     Don't use this method, colornames are mostly X specific"
 
     <context: #return>
 %{
@@ -2923,35 +2923,35 @@
 
     if (ISCONNECTED
      && __isStringLike(aString)) {
-	Display *dpy = myDpy;
-
-	colorname = (char *) __stringVal(aString);
-
-
-	ENTER_XLIB();
-	ok = XParseColor(dpy, DefaultColormap(dpy, screen), colorname, &ecolor);
-	LEAVE_XLIB();
-	if (ok) {
+        Display *dpy = myDpy;
+
+        colorname = (char *) __stringVal(aString);
+
+
+        ENTER_XLIB();
+        ok = XParseColor(dpy, DefaultColormap(dpy, screen), colorname, &ecolor);
+        LEAVE_XLIB();
+        if (ok) {
 #ifdef QUICK_TRUE_COLORS
-	    if (__INST(visualType) == @symbol(TrueColor)) {
-		id = ((ecolor.red >> (16 - __intVal(__INST(bitsRed)))) << __intVal(__INST(redShift))) & __intVal(__INST(redMask));
-		id += ((ecolor.green >> (16 - __intVal(__INST(bitsGreen)))) << __intVal(__INST(greenShift))) & __intVal(__INST(greenMask));
-		id += ((ecolor.blue >> (16 - __intVal(__INST(bitsBlue)))) << __intVal(__INST(blueShift))) & __intVal(__INST(blueMask));
-		RETURN ( __MKSMALLINT(id) );
-	    }
-#endif
-	    ENTER_XLIB();
-	    ok = XAllocColor(dpy, DefaultColormap(dpy, screen), &ecolor);
-	    LEAVE_XLIB();
-	}
-
-	if (! ok) {
-	    RETURN ( nil );
-	}
+            if (__INST(visualType) == @symbol(TrueColor)) {
+                id = ((ecolor.red >> (16 - __intVal(__INST(bitsRed)))) << __intVal(__INST(redShift))) & __intVal(__INST(redMask));
+                id += ((ecolor.green >> (16 - __intVal(__INST(bitsGreen)))) << __intVal(__INST(greenShift))) & __intVal(__INST(greenMask));
+                id += ((ecolor.blue >> (16 - __intVal(__INST(bitsBlue)))) << __intVal(__INST(blueShift))) & __intVal(__INST(blueMask));
+                RETURN ( __MKSMALLINT(id) );
+            }
+#endif
+            ENTER_XLIB();
+            ok = XAllocColor(dpy, DefaultColormap(dpy, screen), &ecolor);
+            LEAVE_XLIB();
+        }
+
+        if (! ok) {
+            RETURN ( nil );
+        }
 #ifdef COUNT_RESOURCES
-	__cnt_color++;
-#endif
-	RETURN ( __MKSMALLINT(ecolor.pixel) );
+        __cnt_color++;
+#endif
+        RETURN ( __MKSMALLINT(ecolor.pixel) );
     }
 %}.
     ^ super colorNamed:aString
@@ -5203,29 +5203,29 @@
     ].
 
     logicalButton isInteger ifTrue:[
-	buttonsPressed := buttonsPressed bitOr:(1 bitShift:logicalButton-1).
+        buttonsPressed := buttonsPressed bitOr:(1 bitShift:logicalButton-1).
     ].
 
     (multiClickTimeDelta notNil and:[lastButtonPressTime notNil]) ifTrue:[
-	time < (lastButtonPressTime + multiClickTimeDelta) ifTrue:[
-	    lastButtonPressTime := time.
-	    self buttonMultiPress:logicalButton x:x y:y view:view.
-	    ^ self.
-	].
+        time < (lastButtonPressTime + multiClickTimeDelta) ifTrue:[
+            lastButtonPressTime := time.
+            self buttonMultiPress:logicalButton x:x y:y view:view.
+            ^ self.
+        ].
     ].
     lastButtonPressTime := time.
 
     view isNil ifTrue:[
-	"/ event arrived, after I destroyed it myself
-	^ self
+        "/ event arrived, after I destroyed it myself
+        ^ self
     ].
     logicalButton == 1 ifTrue:[
-	activateOnClick == true ifTrue:[
-	    "/ dont raise above an active popup view.
-	    (activeKeyboardGrab isNil and:[activePointerGrab isNil]) ifTrue:[
-		view topView raise.
-	    ]
-	].
+        activateOnClick == true ifTrue:[
+            "/ don't raise above an active popup view.
+            (activeKeyboardGrab isNil and:[activePointerGrab isNil]) ifTrue:[
+                view topView raise.
+            ]
+        ].
     ].
     super buttonPress:logicalButton x:x y:y view:view
 !
@@ -6680,24 +6680,21 @@
     "forward a button-press event for some view"
 
     aView isNil ifTrue:[
-	"/ event arrived, after I destroyed it myself
-	^ self
+        "/ event arrived, after I destroyed it myself
+        ^ self
     ].
     button == 1 ifTrue:[
-	activateOnClick == true ifTrue:[
-	    "/ dont raise above an active popup view.
-	    (activeKeyboardGrab isNil and:[activePointerGrab isNil]) ifTrue:[
-		aView topView raise.
+        activateOnClick == true ifTrue:[
+            "/ don't raise above an active popup view.
+            (activeKeyboardGrab isNil and:[activePointerGrab isNil]) ifTrue:[
+                aView topView raise.
 "/            ] ifFalse:[
 "/                activeKeyboardGrab printCR.
 "/                activePointerGrab printCR.
-	    ]
-	].
+            ]
+        ].
     ].
     super buttonPress:button x:x y:y view:aView
-
-
-
 ! !
 
 !XWorkstation methodsFor:'event sending'!
--- a/XftFontDescription.st	Fri Nov 18 20:50:35 2016 +0000
+++ b/XftFontDescription.st	Fri Nov 18 21:26:33 2016 +0000
@@ -1,3 +1,4 @@
+"{ Encoding: utf8 }"
 "{ Package: 'stx:libview' }"
 
 "{ NameSpace: Smalltalk }"
--- a/styles/macosx.style	Fri Nov 18 20:50:35 2016 +0000
+++ b/styles/macosx.style	Fri Nov 18 21:26:33 2016 +0000
@@ -285,3 +285,9 @@
 codeView2.level             0
 
 ;scrolledView.level      0
+
+; activeHelp.backgroundColor       Color rgbValue:16F0F0F0
+activeHelp.borderWidth           1
+activeHelp.borderColor           (Color grey:70)
+activeHelp.font                  (Font family:'helvetica' face:'roman' style:'bold' size:14)
+
--- a/styles/macosx_yosemite.style	Fri Nov 18 20:50:35 2016 +0000
+++ b/styles/macosx_yosemite.style	Fri Nov 18 21:26:33 2016 +0000
@@ -161,3 +161,4 @@
 
 dataSet.labelView.backgroundColor         (Color rgbValue:16rF2F2F2)
 
+launcher.editorLevel        0
--- a/styles/napkin.style	Fri Nov 18 20:50:35 2016 +0000
+++ b/styles/napkin.style	Fri Nov 18 21:26:33 2016 +0000
@@ -115,15 +115,15 @@
 scrollBar.buttonPositions        #around
 scrollBar.spacing                0
 scroller.viewBackground          nil
-scroller.thumbColor              nil
+scroller.thumbColor              Color white
 scroller.thumbEnteredColor       nil
 scroller.thumbActiveColor        nil
-scroller.shadowColor             nil
-scroller.lightColor              nil
-scroller.thumbShadowColor        nil
-scroller.thumbLightColor         nil
+; scroller.shadowColor             nil
+; scroller.lightColor              nil
+; scroller.thumbShadowColor        nil
+; scroller.thumbLightColor         nil
 scroller.NTallyMarks             0
-scroller.thumbFrameColor         nil "/ Color grey:60
+scroller.thumbFrameColor         Color grey:60
 scroller.vista3DStyle            false
 
 arrowButton.leftForm [(Depth8Image new) width: 12; height: 15; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'\
@@ -146,7 +146,6 @@
 @DT!K@@@@@@@GRIAQ#)DHA\@@@@@C1T0P@@@AEHM@@@1R3,>NP@@@DMFI@@.G!@M@@@@@@@NI$,KI#YP@@@@@@@@P DZG2T@@@@@@@@@@C!MKR @@@@@@@@@ \
 @@@SL @@@@@@@@@@@@@@') ; colorMapFromArray:#[134 134 134 29 29 29 173 173 173 67 67 67 204 204 204 212 212 212 91 91 91 101 101 101 235 235 235 240 240 240 125 125 125 133 133 133 154 154 154 171 171 171 194 194 194 202 202 202 83 83 83 219 219 219 229 229 229 234 234 234 239 239 239 123 123 123 130 130 130 153 153 153 165 165 165 62 62 62 73 73 73 211 211 211 217 217 217 228 228 228 105 105 105 110 110 110 121 121 121 129 129 129 145 145 145 164 164 164 190 190 190 201 201 201 81 81 81 216 216 216 227 227 227 233 233 233 238 238 238 244 244 244 142 142 142 163 163 163 186 186 186 200 200 200 79 79 79 215 215 215 225 225 225 232 232 232 237 237 237 243 243 243 140 140 140 162 162 162 185 185 185 198 198 198 207 207 207 86 86 86 223 223 223 103 103 103 108 108 108 114 114 114 139 139 139 32 32 32 183 183 183 197 197 197 206 206 206 214 214 214 94 94 94 231 231 231 236 236 236 242 242 242 135 135 135 160 160 160 49 49 49 68 68 68 77 77 77 84 84 84 222 222 222 230 230 230 107 107 107]; mask:((Depth1Image new) width: 13; height: 15; photometric:(#blackIs0); bitsPerSample:(#[1]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'@@\@A7 G_ _?A>_G8__ ?>G''9<_/A?8G>@_0A<@G') ; yourself); yourself) rotated:90]
 
-
 checkToggle.activeImage      [(Depth8Image new) width: 20; height: 20; photometric:(#palette); bitsPerSample:(#[8]); samplesPerPixel:(1); bits:(ByteArray fromPackedString:'\
 LC@0LC@0LC@0LC@0LC@0LC@0LC@0LC@@@@@@@@@@@@@@@@@@EB\!LC@0LEPFA XFA XFA Y%LEIBC&M,LC@0I PDA@Q%YVU%YS@@LR,>O3@0LCA%YS@0LC@0\
 LC@0PF4[TCP0LC@0LFTFLC@0LC@0L@LQ]#LVA#@0LCA8K$ 0LC@0LCA2L#-QX PFLC@0Q&$JD2(0LC@0OTU9DGD0A@X0LC@RXC)^C@$0LG,BPW\OLC@D@S@0\
@@ -169,12 +168,12 @@
 menu.iconIndicationOff              =checkToggle.passiveImage
 
 
-scroller.verticalThumbFrameImage   [(Depth8Image new) width:18; height:33; bits:(ByteArray fromPackedString:'\
-@@@@@@@A@ LBA@TFA0H@@@@@@@@@@@@H@P$JB0,LCP0NC0@@@@@@@@@P@@@@@@@@@@@T@@@@@@@@@@DQ@@@@@@@@@@@WBP@@@@@@@AH@@@@@@@@@@@@BF@@@\
-@@@@DP@@@@@@@@@@@@@EC@@@@@@@@@@@@@@@@@@@@@@ZF0@@@@@@C0@@@@@@@@@@@@@\GP@@@@@@D08@@@@@@@@@@@@^G0@@@@@@HAH@@@@@@@@@@@@_G @@\
-@@@@@Q$@@@@@@@@@@@@#I@@@@@@@B"T@@@@@@@@@@@@&I0@@@@@@CB @@@@@@@@@@@@)J @@@@@@J1(@@@@@@@@@@@@"A @@@@@@KB4@@@@@@@@@@@@MA0@@\
-@@@@I!0@@@@@@@@@@@@JIP@@@@@@K"<@@@@@@@@@@@@AL@@@@@@@K"<@@@@@@@@@@@@AEP@@@@@@LQ<@@@@@@@@@@@@AFP@@@@@@G1<@@@@@@@@@@@@AFP@@\
-@@@@G1<@@@@@@@@@@@@VFP@@@@@@G3D@@@@@@@@@@@@VFP@@@@@@G3D@@@@@@@@@@@@VFP@@@@@@G3D@@@@@@@@@@@@IFP@@@@@@MA<@@@@@@@@@@@@5FP@@\
-@@@@LQ<@@@@@@@@@@@@!A @@@@@@LSP@@@@@@@@@@@@"F @@@@@@G3\@@@@@@@@@@@@8G@@@@@@@I#$@@@@@@@@@@@@_G0@@@@@@H#(Q@@@@@@@@@@ <B0@@\
-@@@@OQP>O0@@@@@@C2HDE @@@@@@@CXCI14MKR(_AS(&@@@@@@@@@@A@G1(F@0L7JQL@@@@@') ; colorMapFromArray:#[0 0 0 208 208 208 47 40 40 31 24 16 15 0 0 63 56 48 64 64 56 48 48 48 255 248 248 223 216 208 192 192 184 160 160 160 191 176 176 191 184 176 16 16 8 239 232 224 239 224 224 240 240 240 31 16 16 224 224 216 15 8 8 32 24 24 223 208 208 16 16 16 208 200 200 32 32 24 79 72 64 175 168 160 95 88 88 159 144 144 112 112 104 127 120 120 223 216 216 176 176 176 176 176 168 143 136 128 111 104 96 48 40 40 159 152 144 96 88 88 63 56 56 175 160 160 80 72 64 175 168 168 160 152 160 95 80 80 128 128 128 127 112 120 31 24 24 128 120 120 160 152 144 96 96 88 128 128 120 224 216 216 143 136 136 112 104 104 144 144 136 96 96 96 47 32 24 127 112 104 48 48 40 207 192 184 208 208 200 240 232 224 207 200 200]; mask:((Depth1Image new) width:18; height:33; bits:(ByteArray fromPackedString:'A?8@A?<@A@H@C@L@B@L@F@L@B@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@G@\@\
-G <@C?8@A?0@') ; yourself); yourself ]
+;scroller.verticalThumbFrameImage   [(Depth8Image new) width:18; height:33; bits:(ByteArray fromPackedString:'\
+;@@@@@@@A@ LBA@TFA0H@@@@@@@@@@@@H@P$JB0,LCP0NC0@@@@@@@@@P@@@@@@@@@@@T@@@@@@@@@@DQ@@@@@@@@@@@WBP@@@@@@@AH@@@@@@@@@@@@BF@@@\
+;@@@@DP@@@@@@@@@@@@@EC@@@@@@@@@@@@@@@@@@@@@@ZF0@@@@@@C0@@@@@@@@@@@@@\GP@@@@@@D08@@@@@@@@@@@@^G0@@@@@@HAH@@@@@@@@@@@@_G @@\
+;@@@@@Q$@@@@@@@@@@@@#I@@@@@@@B"T@@@@@@@@@@@@&I0@@@@@@CB @@@@@@@@@@@@)J @@@@@@J1(@@@@@@@@@@@@"A @@@@@@KB4@@@@@@@@@@@@MA0@@\
+;@@@@I!0@@@@@@@@@@@@JIP@@@@@@K"<@@@@@@@@@@@@AL@@@@@@@K"<@@@@@@@@@@@@AEP@@@@@@LQ<@@@@@@@@@@@@AFP@@@@@@G1<@@@@@@@@@@@@AFP@@\
+;@@@@G1<@@@@@@@@@@@@VFP@@@@@@G3D@@@@@@@@@@@@VFP@@@@@@G3D@@@@@@@@@@@@VFP@@@@@@G3D@@@@@@@@@@@@IFP@@@@@@MA<@@@@@@@@@@@@5FP@@\
+;@@@@LQ<@@@@@@@@@@@@!A @@@@@@LSP@@@@@@@@@@@@"F @@@@@@G3\@@@@@@@@@@@@8G@@@@@@@I#$@@@@@@@@@@@@_G0@@@@@@H#(Q@@@@@@@@@@ <B0@@\
+;@@@@OQP>O0@@@@@@C2HDE @@@@@@@CXCI14MKR(_AS(&@@@@@@@@@@A@G1(F@0L7JQL@@@@@') ; colorMapFromArray:#[0 0 0 208 208 208 47 40 40 31 24 16 15 0 0 63 56 48 64 64 56 48 48 48 255 248 248 223 216 208 192 192 184 160 160 160 191 176 176 191 184 176 16 16 8 239 232 224 239 224 224 240 240 240 31 16 16 224 224 216 15 8 8 32 24 24 223 208 208 16 16 16 208 200 200 32 32 24 79 72 64 175 168 160 95 88 88 159 144 144 112 112 104 127 120 120 223 216 216 176 176 176 176 176 168 143 136 128 111 104 96 48 40 40 159 152 144 96 88 88 63 56 56 175 160 160 80 72 64 175 168 168 160 152 160 95 80 80 128 128 128 127 112 120 31 24 24 128 120 120 160 152 144 96 96 88 128 128 120 224 216 216 143 136 136 112 104 104 144 144 136 96 96 96 47 32 24 127 112 104 48 48 40 207 192 184 208 208 200 240 232 224 207 200 200]; mask:((Depth1Image new) width:18; height:33; bits:(ByteArray fromPackedString:'A?8@A?<@A@H@C@L@B@L@F@L@B@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@F@L@G@\@\
+;G <@C?8@A?0@') ; yourself); yourself ]