Merge jv
authorMerge Script
Sun, 03 Apr 2016 07:05:07 +0200
branchjv
changeset 16256 65473fc50115
parent 16237 bc32adffa408 (current diff)
parent 16255 5157eb87ee8e (diff)
child 16268 82848a0b6d70
Merge
AboutBox.st
BrowserView.st
CodeGeneratorTool.st
DebugView.st
Diff3TextView.st
DiffTextView.st
EventMonitor.st
MemoryMonitorView.st
MemoryUsageView.st
SmalltalkCodeGeneratorTool.st
SystemBrowser.st
Tools__CodeView2.st
Tools__MethodList.st
Tools__NewSystemBrowser.st
WorkspaceApplication.st
extensions.st
stx_libtool.st
--- a/AboutBox.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/AboutBox.st	Sun Apr 03 07:05:07 2016 +0200
@@ -188,7 +188,7 @@
 initialize
     "setup the box; change all of my components viewBackground to some darkish grey."
 
-    |dark green lbl graphicsDevice|
+    |dark green lbl|
 
     super initialize.
 
@@ -196,8 +196,8 @@
 
     green := self class defaultGreen.    
     dark := Color grey:20.
-    (graphicsDevice := self graphicsDevice) hasColors ifFalse:[
-        graphicsDevice hasGrayscales ifTrue:[
+    device hasColors ifFalse:[
+        device hasGrayscales ifTrue:[
             green := Color brightness:(green brightness).    
             dark := Color brightness:(dark brightness).    
         ] ifFalse:[
--- a/BrowserView.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/BrowserView.st	Sun Apr 03 07:05:07 2016 +0200
@@ -7405,7 +7405,7 @@
 
     |untranslatedKey|
 
-    untranslatedKey := self graphicsDevice keyboardMap keyAtValue:key ifAbsent:key.
+    untranslatedKey := device keyboardMap keyAtValue:key ifAbsent:key.
 
     view == classCategoryListView ifTrue:[
         (key == #Find) ifTrue:[^ true].
@@ -7453,7 +7453,7 @@
     "/
     "/ have to untranslate (since we get #Inspect / #Search
     "/
-    untranslatedKey := self graphicsDevice keyboardMap keyAtValue:key ifAbsent:key.
+    untranslatedKey := device keyboardMap keyAtValue:key ifAbsent:key.
 
     view == classCategoryListView ifTrue:[
         (key == #Find) ifTrue:[^ self classCategoryFindClass].
@@ -13243,10 +13243,10 @@
             "/ Icons at:name put:icn.
         ].
         h := icn height.
-        h > (fh := SelectionInListView defaultFont heightOn:self graphicsDevice) ifTrue:[
+        h > (fh := SelectionInListView defaultFont heightOn:device) ifTrue:[
             icn := icn magnifiedBy:(fh / h)
         ].
-        icn onDevice:self graphicsDevice
+        icn onDevice:device
       ]
 
     "
@@ -13506,7 +13506,7 @@
                             cls := actualClass.
 
                             codeView modified ifFalse:[
-                                Screen currentScreenQuerySignal answer:self graphicsDevice
+                                Screen currentScreenQuerySignal answer:device
                                 do:[
                                     newCode := highlighter formatMethodSource:oldCode in:cls.
                                 ].
--- a/CodeGeneratorTool.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/CodeGeneratorTool.st	Sun Apr 03 07:05:07 2016 +0200
@@ -311,8 +311,16 @@
     ^ self new createInstanceCreationMethodWithSetupFor:selector category:category in:aMetaClass
 !
 
+createMultiSetterInstanceCreationMethodFor:aCollectionOfVarNames in:aClass
+    "create a multi-setter instance creator method for instvars.
+     This creates a multi setter method (a:val1 b:val2 c:val3...)
+     and a corresponding new method on the class side."
+
+    ^ self new createMultiSetterInstanceCreationMethodFor:aCollectionOfVarNames in:aClass
+!
+
 createMultiSetterMethodFor:aCollectionOfVarNames in:aClass
-    "create a multi-setter method for instvars."
+    "create a multi-setter method (a:val1 b:val2 c:val3...) for instvars."
 
     ^ self new createMultiSetterMethodFor:aCollectionOfVarNames in:aClass
 !
@@ -1489,8 +1497,16 @@
     self subclassResponsibility
 !
 
+createMultiSetterInstanceCreationMethodFor:aCollectionOfVarNames in:aClass
+    "create a multi-setter instance creator method for instvars.
+     This creates a multi setter method (a:val1 b:val2 c:val3...)
+     and a corresponding new method on the class side."
+
+    self subclassResponsibility
+!
+
 createMultiSetterMethodFor:aCollectionOfVarNames in:aClass
-    "create a multi-setter method for instvars."
+    "create a multi-setter method (a:val1 b:val2 c:val3...) for instvars."
 
     self subclassResponsibility
 !
--- a/DebugView.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/DebugView.st	Sun Apr 03 07:05:07 2016 +0200
@@ -2103,7 +2103,7 @@
 
     "/ restore the previous pointer grab
     grabber notNil ifTrue:[
-        self graphicsDevice grabPointerInView:grabber.
+        device grabPointerInView:grabber.
         grabber := nil.
     ].
 
@@ -2498,17 +2498,17 @@
     continueButton preferredExtent:(w @ continueButton preferredHeight).
 
     aProcess state == #run ifTrue:[
-	self graphicsDevice hasColors ifTrue:[
-	    continueButton foregroundColor:Color red darkened.
-	].
-	continueButton label:(resources string:'Stop').
-	continueButton action:[self doStop].
+        device hasColors ifTrue:[
+            continueButton foregroundColor:Color red darkened.
+        ].
+        continueButton label:(resources string:'Stop').
+        continueButton action:[self doStop].
     ] ifFalse:[
-	self graphicsDevice hasColors ifTrue:[
-	    continueButton foregroundColor:Color green darkened darkened.
-	].
-	continueButton label:(resources string:'Continue').
-	continueButton action:[self doContinue].
+        device hasColors ifTrue:[
+            continueButton foregroundColor:Color green darkened darkened.
+        ].
+        continueButton label:(resources string:'Continue').
+        continueButton action:[self doContinue].
     ].
     continueButton preferredExtent:(w @ continueButton preferredHeight).
 
@@ -2522,9 +2522,9 @@
 "/    sendButton destroy.
 
     updateButton := Button
-			label:(resources string:'Update')
-			action:[self updateContext]
-			in:bpanel.
+                        label:(resources string:'Update')
+                        action:[self updateContext]
+                        in:bpanel.
     monitorToggle := Toggle in:bpanel.
     monitorToggle label:(resources string:'Monitor').
     monitorToggle pressAction:[self autoUpdateOn].
@@ -2543,33 +2543,33 @@
     nextOutButton notNil ifTrue:[nextOutButton disable; beInvisible].
 
     aProcess isNil ifTrue:[
-	terminateButton disable.
-	abortButton disable.
-	continueButton disable.
-	returnButton disable.
-	restartButton disable.
+        terminateButton disable.
+        abortButton disable.
+        continueButton disable.
+        returnButton disable.
+        restartButton disable.
     ] ifFalse:[
-	(aProcess suspendedContext isNil
-	or:[aProcess isSystemProcess]) ifTrue:[
-	    terminateButton disable.
-	].
-
-	self setContextSkippingInterruptContexts:aProcess suspendedContext.
-
-	catchBlock := [
-	    catchBlock := nil.
-	    contextArray := nil.
-	    selectedContext := actualContext := firstContext := nil.
-	    steppedContext := wrapperContext := nil.
-
-	    (exitAction == #terminate) ifTrue:[
-		aProcess terminate.
-	    ].
-	    (exitAction == #quickTerminate) ifTrue:[
-		aProcess terminateNoSignal.
-	    ].
-	    super destroy
-	].
+        (aProcess suspendedContext isNil
+        or:[aProcess isSystemProcess]) ifTrue:[
+            terminateButton disable.
+        ].
+
+        self setContextSkippingInterruptContexts:aProcess suspendedContext.
+
+        catchBlock := [
+            catchBlock := nil.
+            contextArray := nil.
+            selectedContext := actualContext := firstContext := nil.
+            steppedContext := wrapperContext := nil.
+
+            (exitAction == #terminate) ifTrue:[
+                aProcess terminate.
+            ].
+            (exitAction == #quickTerminate) ifTrue:[
+                aProcess terminateNoSignal.
+            ].
+            super destroy
+        ].
     ].
     self open
 
@@ -2626,8 +2626,8 @@
     aComponent == codeView ifTrue:[
         |point localPoint|
 
-        point := self device pointerPosition.
-        localPoint := self device translatePointFromRoot:point toView:codeView.
+        point := device pointerPosition.
+        localPoint := device translatePointFromRoot:point toView:codeView.
         ((localPoint x between:0 and:codeView width)
         and:[localPoint y between:0 and:codeView height])
         ifTrue:[
@@ -4839,59 +4839,59 @@
     |proc exContext ex answer|
 
     self checkIfCodeIsReallyModified ifTrue:[
-	(self confirm:('Code modified - continue anyway ?')) ifFalse:[
-	    ^ self
-	]
+        (self confirm:('Code modified - continue anyway ?')) ifFalse:[
+            ^ self
+        ]
     ].
 
     inspecting ifTrue:[
-	self graphicsDevice hasColors ifTrue:[
-	    continueButton foregroundColor:Color red darkened.
-	].
-	continueButton label:(resources string:'Stop').
-	continueButton action:[self doStop].
-
-	self processPerform:#resume.
-
-	^ self
+        device hasColors ifTrue:[
+            continueButton foregroundColor:Color red darkened.
+        ].
+        continueButton label:(resources string:'Stop').
+        continueButton action:[self doStop].
+
+        self processPerform:#resume.
+
+        ^ self
     ].
     canContinue ifTrue:[
-	exContext := thisContext findSpecialHandle:false raise:true.
-
-	(exContext notNil
-	and:[ (ex := exContext receiver) isLazyValue not
-	and:[ ex isException
-	and:[ ex creator == NoHandlerError
-	and:[ ex exception creator == RecursionError]]]])
-	ifTrue:[
-	    "/ debug due to unhandled recursionInterrupt.
-	    "/ ask if we should proceed with more stack.
-
-	    answer := self confirm:'Debugger entered due to a stack overflow.\\Continue with more stack ?' withCRs.
-	    answer == true ifTrue:[
-		proc := Processor activeProcess.
-		proc setMaximumStackSize:(proc maximumStackSize * 2).
-	    ].
-	].
-
-	steppedContext := wrapperContext := nil.
-	tracing := false.
-	haveControl := false.
-	exitAction := #continue.
-
-	"exit private event-loop"
-	catchBlock value.
-
-	"/ not reached.
-	'DebugView [warning]: continue failed' errorPrintCR.
-	continueButton turnOff.
+        exContext := thisContext findSpecialHandle:false raise:true.
+
+        (exContext notNil
+        and:[ (ex := exContext receiver) isLazyValue not
+        and:[ ex isException
+        and:[ ex creator == NoHandlerError
+        and:[ ex exception creator == RecursionError]]]])
+        ifTrue:[
+            "/ debug due to unhandled recursionInterrupt.
+            "/ ask if we should proceed with more stack.
+
+            answer := self confirm:'Debugger entered due to a stack overflow.\\Continue with more stack ?' withCRs.
+            answer == true ifTrue:[
+                proc := Processor activeProcess.
+                proc setMaximumStackSize:(proc maximumStackSize * 2).
+            ].
+        ].
+
+        steppedContext := wrapperContext := nil.
+        tracing := false.
+        haveControl := false.
+        exitAction := #continue.
+
+        "exit private event-loop"
+        catchBlock value.
+
+        "/ not reached.
+        'DebugView [warning]: continue failed' errorPrintCR.
+        continueButton turnOff.
 
     ] ifFalse:[
-	inspecting ifFalse:[
-	    'DebugView [info]: resuming top context' infoPrintCR.
-	    self showSelection:1.
-	    self doReturn
-	]
+        inspecting ifFalse:[
+            'DebugView [info]: resuming top context' infoPrintCR.
+            self showSelection:1.
+            self doReturn
+        ]
     ]
 
     "Modified: / 5.10.1998 / 13:03:47 / cg"
@@ -5435,15 +5435,15 @@
     "stop the process (if its running, otherwise this is a no-op)"
 
     inspecting ifTrue:[
-	self graphicsDevice hasColors ifTrue:[
-	    continueButton foregroundColor:Color green darkened darkened.
-	].
-	continueButton label:(resources string:'Continue').
-	continueButton action:[self doContinue].
-
-	self processPerform:#stop.
-
-	^ self
+        device hasColors ifTrue:[
+            continueButton foregroundColor:Color green darkened darkened.
+        ].
+        continueButton label:(resources string:'Continue').
+        continueButton action:[self doContinue].
+
+        self processPerform:#stop.
+
+        ^ self
     ].
 
     "Modified: 20.10.1996 / 18:30:48 / cg"
@@ -7196,7 +7196,7 @@
      Otherwise, the GC will not be able to release it."
 
     windowGroup notNil ifTrue:[
-	windowGroup setProcess:nil.
+        windowGroup setProcess:nil.
     ].
 
     self releaseDebuggee.
@@ -7206,16 +7206,16 @@
     "/
     "/ only cache if I am on the Display (i.e. the default screen)
     "/
-    self graphicsDevice == Display ifTrue:[
-	exclusive ifTrue:[
-	    CachedExclusive := self
-	] ifFalse:[
-	    CachedDebugger := self
-	].
+    device == Display ifTrue:[
+        exclusive ifTrue:[
+            CachedExclusive := self
+        ] ifFalse:[
+            CachedDebugger := self
+        ].
     ].
 
     ObjectMemory stepInterruptHandler == self ifTrue:[
-	ObjectMemory stepInterruptHandler:nil
+        ObjectMemory stepInterruptHandler:nil
     ].
 
     "Modified: 10.7.1997 / 15:50:46 / stefan"
@@ -8108,7 +8108,7 @@
 "/                self showError:ex description.
 "/                ex proceed.
 "/            ] do:[
-                self graphicsDevice
+                device
                     dispatchModalWhile:[
                         Processor activeProcess state:#debug.
                         haveControl].
@@ -8218,7 +8218,7 @@
         ] do:[
             "/ make certain that sub-debuggers, inspectors etc.
             "/ come up on my device.
-            Screen currentScreenQuerySignal answer:self graphicsDevice
+            Screen currentScreenQuerySignal answer:device
             do:[
                 Dialog aboutToOpenBoxNotificationSignal
                     handle:[:ex | ex proceed ]
--- a/Diff3TextView.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/Diff3TextView.st	Sun Apr 03 07:05:07 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libtool' }"
 
+"{ NameSpace: Smalltalk }"
+
 ThreeColumnTextView subclass:#Diff3TextView
 	instanceVariableNames:'useColors showSeparators addedColor addedBgColor removedColor
 		removedBgColor changedColor changedBgColor'
@@ -290,19 +292,19 @@
 
     useColors := true.
     useColors ifTrue:[
-	self graphicsDevice hasColors ifTrue:[
-	    addedColor := Color black.
-	    addedBgColor := Color green.
+        device hasColors ifTrue:[
+            addedColor := Color black.
+            addedBgColor := Color green.
 
-	    removedColor := Color white.
-	    removedBgColor := Color red.
+            removedColor := Color white.
+            removedBgColor := Color red.
 
-	    changedColor := Color white.
-	    changedBgColor := Color blue.
-	] ifFalse:[
-	    addedBgColor := removedBgColor := changedBgColor := Color black.
-	    addedColor := removedColor := changedColor := Color white.
-	]
+            changedColor := Color white.
+            changedBgColor := Color blue.
+        ] ifFalse:[
+            addedBgColor := removedBgColor := changedBgColor := Color black.
+            addedColor := removedColor := changedColor := Color white.
+        ]
     ].
 
     "Created: 16.11.1995 / 16:59:48 / cg"
@@ -437,5 +439,6 @@
 !Diff3TextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/Diff3TextView.st,v 1.10 2014-04-17 23:22:39 stefan Exp $'
+    ^ '$Header$'
 ! !
+
--- a/DiffTextView.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/DiffTextView.st	Sun Apr 03 07:05:07 2016 +0200
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libtool' }"
 
+"{ NameSpace: Smalltalk }"
+
 TwoColumnTextView subclass:#DiffTextView
 	instanceVariableNames:'useColors showSeparators addedColor addedBgColor removedColor
 		removedBgColor changedColor changedBgColor changedSpacesOnlyColor
@@ -247,7 +249,7 @@
 
     showSeparators := false.
 
-    (useColors := self graphicsDevice hasColors) ifTrue:[
+    (useColors := device hasColors) ifTrue:[
         addedColor := Color white.
         addedBgColor := Color red.
 
@@ -262,7 +264,7 @@
     ] ifFalse:[
         showSeparators := true.
 
-        (useColors := self graphicsDevice hasGreyscales) ifTrue:[
+        (useColors := device hasGreyscales) ifTrue:[
             addedBgColor := removedBgColor := changedBgColor := Color grey:80.
             addedColor := removedColor := changedColor := Color black.
         ] ifFalse:[
@@ -677,10 +679,10 @@
 !DiffTextView class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/DiffTextView.st,v 1.66 2014-12-11 20:49:11 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libtool/DiffTextView.st,v 1.66 2014-12-11 20:49:11 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/EventMonitor.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/EventMonitor.st	Sun Apr 03 07:05:07 2016 +0200
@@ -580,7 +580,7 @@
              , ' (' , key asciiValue printString , ')'.
     ] ifFalse:[
         s := ' symbolic key:' , key storeString.
-        untranslatedKey := self graphicsDevice keyboardMap keyAtValue:key ifAbsent:key.
+        untranslatedKey := device keyboardMap keyAtValue:key ifAbsent:key.
         untranslatedKey ~~ key ifTrue:[
             s := s , ' untranslated key:' , untranslatedKey storeString
         ].
@@ -621,7 +621,7 @@
         ' (' printOn:outputStream. key asciiValue printOn:outputStream. ')' printOn:outputStream
     ] ifFalse:[
         ' symbolic key:' print. key storeString printOn:outputStream.
-        untranslatedKey := self graphicsDevice keyboardMap keyAtValue:key ifAbsent:key.
+        untranslatedKey := device keyboardMap keyAtValue:key ifAbsent:key.
         untranslatedKey ~~ key ifTrue:[
             ' untranslated key:' printOn:outputStream. untranslatedKey storeString printOn:outputStream
         ]
@@ -725,6 +725,6 @@
 !EventMonitor class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libtool/EventMonitor.st,v 1.32 2014-03-20 12:53:40 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/MemoryMonitorView.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/MemoryMonitorView.st	Sun Apr 03 07:05:07 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
@@ -626,7 +624,7 @@
 
     updateIndex := 1.
 
-    self font:((Font family:'courier' face:'medium' style:'roman' size:10) onDevice:self device).
+    self font:((Font family:'courier' face:'medium' style:'roman' size:10) onDevice:device).
     org := gc font widthOf:'max 99999k '.
     level := 0.
 
@@ -636,7 +634,7 @@
 
     viewBackground := self blackColor.
 
-    self graphicsDevice hasColors ifTrue:[
+    device hasColors ifTrue:[
         newColor := Color orange. "/ yellow.
         freeColor := Color green.
         mallocColor := Color yellow.
@@ -681,7 +679,7 @@
         ].
     ].
 
-    graphicsDevice := self graphicsDevice.
+    graphicsDevice := device.
     newColor := newColor onDevice:graphicsDevice.
     freeColor := freeColor onDevice:graphicsDevice.
     oldColor := oldColor onDevice:graphicsDevice.
--- a/MemoryUsageView.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/MemoryUsageView.st	Sun Apr 03 07:05:07 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
 	      All Rights Reserved
@@ -171,7 +169,7 @@
     titleLabel font:(EditTextView defaultFont).
     list menuHolder:self; menuPerformer:self; menuMessage:#usageMenu.
 
-    self extent:((list font widthOf:headLine) + (self device horizontalPixelPerMillimeter * 15) rounded) @ self height.
+    self extent:((list font widthOf:headLine) + ( device horizontalPixelPerMillimeter * 15) rounded) @ self height.
 
     "
      MemoryUsageView open
--- a/SmalltalkCodeGeneratorTool.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/SmalltalkCodeGeneratorTool.st	Sun Apr 03 07:05:07 2016 +0200
@@ -2033,6 +2033,27 @@
     ].
 !
 
+createMultiSetterInstanceCreationMethodFor:aCollectionOfVarNames in:aClass
+    "create a multi-setter instance creator method for instvars."
+
+    |argPart source|
+    
+    self createMultiSetterMethodFor:aCollectionOfVarNames in:aClass.
+    
+    source := ''.
+    aCollectionOfVarNames do:[:eachVar |
+        source := source , (eachVar , ':' , eachVar , 'Arg ').
+    ].
+    argPart := source.
+    
+    source := source , Character cr.
+    (userPreferences generateCommentsForSetters) ifTrue:[
+        source := source , ('    "return a new instance with multiple instance variables initialized"' , Character cr , Character cr).
+    ].
+    source := source , ('    ^ self new ' , argPart).
+    self compile:source forClass:aClass theMetaclass inCategory:#'instance creation'.
+!
+
 createMultiSetterMethodFor:aCollectionOfVarNames in:aClass
     "create a multi-setter method for instvars."
 
--- a/SystemBrowser.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/SystemBrowser.st	Sun Apr 03 07:05:07 2016 +0200
@@ -6181,7 +6181,7 @@
     "return all instance- (if wantInst is true) and/or classmethods (if wantClass is true) 
      from classes in aCollectionOfClasses, where aBlock evaluates to true."
 
-    |list checkedClasses checkBlock nClasses nClassesDone|
+    |list checkedClasses checkBlock nClasses nClassesDone oldPercentage newPercentage|
 
     checkedClasses := IdentitySet new.
     list := OrderedCollection new.
@@ -6211,7 +6211,8 @@
 
     nClasses := aCollectionOfClasses size.
     nClassesDone := 0.
-
+    oldPercentage := 0.
+    
     aCollectionOfClasses do:[:aClass |
         (aClass notNil and:[aClass isObsolete not]) ifTrue:[
             "
@@ -6228,7 +6229,11 @@
             ].
             nClassesDone > 5 ifTrue:[
                 "/ Processor yield
-                ProgressNotification progressPercentage:(nClassesDone / nClasses)*100.
+                newPercentage := nClassesDone * 100 // nClasses.
+                newPercentage ~= oldPercentage ifTrue:[
+                    ProgressNotification progressPercentage:newPercentage.
+                    oldPercentage := newPercentage.
+                ].
             ].
         ].
         nClassesDone := nClassesDone + 1.
--- a/Tools__CodeView2.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/Tools__CodeView2.st	Sun Apr 03 07:05:07 2016 +0200
@@ -2736,9 +2736,9 @@
     cancelColor := Color red.
     diffColor := Color yellow.
 
-    acceptColor := acceptColor lighter onDevice:self graphicsDevice.
-    cancelColor := cancelColor lighter lighter onDevice:self graphicsDevice.
-    diffColor := diffColor lighter lighter onDevice:self graphicsDevice.
+    acceptColor := acceptColor lighter onDevice:device.
+    cancelColor := cancelColor lighter lighter onDevice:device.
+    diffColor := diffColor lighter lighter onDevice:device.
 
     self enableMotionEvents.   "/ for per-line tooltips
 
@@ -2949,14 +2949,15 @@
      Color of drawn objects should be taken from lineFont, lineColor"
 
     |lineString yTop yBaseline fontAscent fontDescent
-     textW requiredW oldFont newFont oldColor newColor myFont|
+     textW requiredW oldFont newFont oldColor newColor myFont textViewFont|
 
     shown ifFalse:[ ^ self ]. "/ Do not bother if the view is not shown.
     textView isNil ifTrue:[^ self].     "/ happens when shown in UIPainter
-
+        
     requiredW := self width.
     myFont := gc font.
-
+    textViewFont := textView font.
+    
     showLineNumbers ifTrue:[
         lineString := self displayedString:line.
 
@@ -2974,8 +2975,8 @@
         ].
         newFont ~~ oldFont ifTrue:[
             "/ ensure that the line number lines are not higher than the text lines
-            (newFont heightOn:self graphicsDevice) > (textView font heightOn:self graphicsDevice) ifTrue:[
-                newFont := textView font.
+            (newFont heightOn:device) > (textViewFont heightOn:device) ifTrue:[
+                newFont := textViewFont.
             ].
             newFont ~~ oldFont ifTrue:[
                 self font:newFont.
@@ -2984,9 +2985,8 @@
         ].
     ].
 
-    fontAscent := textView font ascentOn:self graphicsDevice.
-    fontDescent := textView font descentOn:self graphicsDevice.
-
+    fontAscent := textViewFont ascentOn:device.
+    fontDescent := textViewFont descentOn:device.
 
     yTop := (self yOfTextViewLine:line) ? 0.
     yBaseline := yTop + fontAscent.
--- a/Tools__MethodList.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/Tools__MethodList.st	Sun Apr 03 07:05:07 2016 +0200
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2000 by eXept Software AG
 	      All Rights Reserved
@@ -16,10 +14,11 @@
 "{ NameSpace: Tools }"
 
 BrowserList subclass:#MethodList
-	instanceVariableNames:'classes selectedMethodNameIndices methodList lastSelectedMethods
-		browserNameList variableFilter filterClassVars updateProcess
-		lastShowClass lastShowCategory lastShowClassFirst
-		showMethodInheritance lastMethodClass lastMethodClassesSubclasses
+	instanceVariableNames:'classes selectedMethodNameIndices methodList methodNameList
+		lastSelectedMethods browserNameList variableFilter
+		filterClassVars updateProcess lastShowClass lastShowCategory
+		lastShowClassFirst showMethodInheritance lastMethodClass
+		lastMethodClassesSubclasses
 		classAndSelectorsRedefinedBySubclassesOfClass showClass
 		showMethodComplexity showMethodTypeIcon
 		showImageResourceMethodsImages showSyntheticMethods'
@@ -1238,51 +1237,43 @@
         ].
     ].
     methods := OrderedCollection new:(entries size).
+    methodNameList := OrderedCollection new:(entries size).
 
-    "/ first generate the new methodList, and see if it is different ...
+    newNameList := OrderedCollection new:(entries size).
+
+    "/ multiple classes must add the className for some
 
     entries do:[:entry |
-        |sel mthd|
+        |cls sel mthd s needClass|
 
+        cls := entry at:1.
+        sel := entry at:2.
         mthd := entry at:3.
-        methods add:mthd.
-    ].
-    false "methodList = methods" "does not care for changed icons" ifTrue:[
-        "/ same list
-        newNameList := self browserNameList.
-    ] ifFalse:[
-        newNameList := OrderedCollection new:(entries size).
-
-        "/ multiple classes must add the className for some
-
-        entries do:[:entry |
-            |cls sel mthd s needClass|
-
-            cls := entry at:1.
-            sel := entry at:2.
-            mthd := entry at:3.
-            needClass := doShowClass.
+        needClass := doShowClass.
 
 "/        needClass ifFalse:[
 "/            needClass := (selectorBag occurrencesOf:sel) > 1
 "/        ].
-            (suppressInheritanceInfoNow not
-            and:[ (Timestamp now secondDeltaFrom:startTime) > 3 ]) ifTrue:[
-                suppressInheritanceInfoNow := true.
-            ].
+        (suppressInheritanceInfoNow not
+        and:[ (Timestamp now secondDeltaFrom:startTime) > 3 ]) ifTrue:[
+            suppressInheritanceInfoNow := true.
+        ].
 
-            s := self
-                    listEntryForMethod:mthd
-                    selector:sel
-                    class:cls
-                    showClass:needClass
-                    showCategory:doShowCategory
-                    classFirst:doShowClassFirst
-                    suppressInheritanceInfo:suppressInheritanceInfoNow.
+        s := self
+                listEntryForMethod:mthd
+                selector:sel
+                class:cls
+                showClass:needClass
+                showCategory:doShowCategory
+                classFirst:doShowClassFirst
+                suppressInheritanceInfo:suppressInheritanceInfoNow.
 
-            newNameList add:s.
-        ].
+        newNameList add:s.
+
+        methods add:mthd.
+        methodNameList add:{ cls name . sel}.
     ].
+    
     self makeIndependent.
     classes := newClasses.
     self makeDependent.
--- a/Tools__NewSystemBrowser.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/Tools__NewSystemBrowser.st	Sun Apr 03 07:05:07 2016 +0200
@@ -12709,6 +12709,12 @@
                   showBusyCursorWhilePerforming: true
                 )
                (MenuItem
+                  enabled: canGenerateMultiSetterInstanceCreationMethodHolder
+                  label: 'Multi-Setter Instance Creation Method'
+                  itemValue: variablesMenuGenerateMultiSetterInstanceCreationMethod
+                  showBusyCursorWhilePerforming: true
+                )
+               (MenuItem
                   label: '-'
                   isVisible: hasNonMetaSelectedHolder
                 )
@@ -20762,6 +20768,10 @@
     ^ [ self canGenerateAspectMethod ]
 !
 
+canGenerateMultiSetterInstanceCreationMethodHolder
+    ^ self hasSingleLoadedClassSelectedAndMultipleVariablesSelectedHolder
+!
+
 canGenerateMultiSetterMethodHolder
     ^ self hasSingleLoadedClassSelectedAndMultipleVariablesSelectedHolder
 !
@@ -30464,6 +30474,23 @@
         ].
 !
 
+classMenuGenerateMultiSetterInstanceCreationMethod
+    "create a multi setter instance creation method for selected instvars."
+
+    |cls vars|
+
+    cls := self theSingleSelectedClass.
+    vars := cls allInstVarNames
+            select:[:var | self selectedVariables value includes:var].
+
+    self
+        generateUndoableChange:'Generate multi-setter instance creator'
+        overClasses:(Array with:cls)
+        via:[:generator :eachClass |
+            generator createMultiSetterInstanceCreationMethodFor:vars in:cls
+        ].
+!
+
 classMenuGenerateMultiSetterMethod
     "create a multi setter method for selected instvars."
 
@@ -34054,6 +34081,12 @@
     "Created: / 28-02-2012 / 09:07:39 / cg"
 !
 
+variablesMenuGenerateMultiSetterInstanceCreationMethod
+    "create a multi setter instance creation method for selected instvars."
+
+    self classMenuGenerateMultiSetterInstanceCreationMethod
+!
+
 variablesMenuGenerateMultiSetterMethod
     "create a multi setter method for selected instvars."
 
@@ -58449,6 +58482,7 @@
     "Created: / 04-12-2011 / 22:22:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !NewSystemBrowser methodsFor:'private-semantic checks'!
 
 checkAcceptedMethod:aMethod inClass:aClass
--- a/WorkspaceApplication.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/WorkspaceApplication.st	Sun Apr 03 07:05:07 2016 +0200
@@ -4486,17 +4486,17 @@
 "/        needRemove := false.
 "/    ].
 
-    self graphicsDevice platformName = 'X11' ifTrue:[
+    device platformName = 'X11' ifTrue:[
         font := Font family:'unifont' face:'medium' style:'roman' size:16 encoding:'iso10646-1'.
-        font := font onDevice:self graphicsDevice ifAbsent:nil.
+        font := font onDevice:device ifAbsent:nil.
         font isNil ifTrue:[    
             font := Font family:'arial' face:'medium' style:'roman' size:12 encoding:'iso10646-1'.
-            font := font onDevice:self graphicsDevice ifAbsent:nil.
+            font := font onDevice:device ifAbsent:nil.
         ].
     ] ifFalse:[
         "/ font := Font family:'Arial Unicode MS' face:'medium' style:'roman' size:10 encoding:'ms-ansi'.
         font := Font family:'arial' face:'medium' style:'roman' size:10 encoding:'ms-ansi'.
-        font := font onDevice:self graphicsDevice ifAbsent:nil.
+        font := font onDevice:device ifAbsent:nil.
     ].
 
     #(  "/ file                     resourceKey             title                       forcedEncoding  type
--- a/extensions.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/extensions.st	Sun Apr 03 07:05:07 2016 +0200
@@ -39,6 +39,25 @@
     ^ #timeClassBrowserIcon
 ! !
 
+!ApplicationModel methodsFor:'debugging'!
+
+inspectorExtraAttributes
+    |atts|
+
+    atts := super inspectorExtraAttributes.
+    builder notNil ifTrue:[
+        builder namedComponents keysAndValuesDo:[:eachName :eachWidget |
+            atts add:('-[: ',eachName,' :]') -> [ builder namedComponents at:eachName ].
+        ].
+        builder bindings notNil ifTrue:[
+            builder bindings keysAndValuesDo:[:eachName :eachAspect |
+                atts add:('-~> ',eachName) -> [ builder bindings at:eachName ].
+            ].
+        ].
+    ].
+    ^ atts
+! !
+
 !ArrayedCollection methodsFor:'inspecting'!
 
 inspector2TabForHexDump
--- a/stx_libtool.st	Sat Apr 02 06:55:28 2016 +0200
+++ b/stx_libtool.st	Sun Apr 03 07:05:07 2016 +0200
@@ -427,6 +427,7 @@
      A correponding method with real names must be present in my concrete subclasses"
 
     ^ #(
+        ApplicationModel inspectorExtraAttributes
         ArrayedCollection inspector2TabForHexDump
         Bag inspectorExtraAttributes
         Behavior iconInBrowserSymbol