Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 23 Apr 2015 08:04:13 +0100
branchjv
changeset 18274 042d13555f1f
parent 18261 22bdfc405bca (current diff)
parent 18273 7f1f1a4eef6b (diff)
child 18276 07269d05da24
Merge
Array.st
Character.st
CharacterArray.st
CharacterWriteStream.st
Collection.st
Context.st
Date.st
Filename.st
Object.st
PeekableStream.st
ReadStream.st
UserPreferences.st
--- a/Array.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/Array.st	Thu Apr 23 08:04:13 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -301,7 +303,6 @@
     "Modified: 23.4.1996 / 15:55:06 / cg"
 ! !
 
-
 !Array methodsFor:'accessing'!
 
 at:index
@@ -1748,54 +1749,54 @@
     "append a printed representation of the receiver to aStream"
 
     self isLiteral ifTrue:[
-	|limit firstOne s|
+        |limit firstOne s|
 
-	thisContext isRecursive ifTrue:[
-	    'Array [error]: printOn: of self referencing collection.' errorPrintCR.
-	    aStream nextPutAll:'#("recursive")'.
-	    ^ self
-	].
+        thisContext isRecursive ifTrue:[
+            'Array [error]: printOn: of self referencing collection.' errorPrintCR.
+            aStream nextPutAll:'#("recursive")'.
+            ^ self
+        ].
 
-	aStream nextPutAll:'#('.
-	firstOne := true.
+        aStream nextPutAll:'#('.
+        firstOne := true.
 
-	"
-	 if aStream is not positionable, create an temporary positionable stream
-	 (needed for limit calculation)
-	"
-	aStream isPositionable ifTrue:[
-	    s := aStream.
-	] ifFalse:[
-	    s := WriteStream on:(String uninitializedNew:50).
-	].
-	limit := s position + self maxPrint.
+        "
+         if aStream is not positionable, create an temporary positionable stream
+         (needed for limit calculation)
+        "
+        aStream isPositionable ifTrue:[
+            s := aStream.
+        ] ifFalse:[
+            s := CharacterWriteStream new:50.
+        ].
+        limit := s position + self maxPrint.
 
-	self printElementsDo:[:element |
-	    firstOne ifFalse:[
-		s space
-	    ] ifTrue:[
-		firstOne := false
-	    ].
-	    (s position >= limit) ifTrue:[
-		s ~~ aStream ifTrue:[
-		    aStream nextPutAll:(s contents).
-		].
-		aStream nextPutAll:'...etc...)'.
-		^ self
-	    ] ifFalse:[
-		element printOn:s.
-	    ].
-	].
-	s ~~ aStream ifTrue:[
-	    aStream nextPutAll:(s contents).
-	].
-	aStream nextPut:$)
+        self printElementsDo:[:element |
+            firstOne ifFalse:[
+                s space
+            ] ifTrue:[
+                firstOne := false
+            ].
+            (s position >= limit) ifTrue:[
+                s ~~ aStream ifTrue:[
+                    aStream nextPutAll:(s contents).
+                ].
+                aStream nextPutAll:'...etc...)'.
+                ^ self
+            ] ifFalse:[
+                element printOn:s.
+            ].
+        ].
+        s ~~ aStream ifTrue:[
+            aStream nextPutAll:(s contents).
+        ].
+        aStream nextPut:$)
     ] ifFalse:[
-	super printOn:aStream
+        super printOn:aStream
     ]
 
     "
-     #(1 2 $a 'hello' sym kewordSymbol:with: #'funny symbol') printString
+     #(1 2 $a $Å  'hello' sym kewordSymbol:with: #'funny symbol') printString
      #(1 2 $a [1 2 3] true false nil #true #false #nil) printString
     "
 
@@ -2647,9 +2648,10 @@
 !Array class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Array.st,v 1.166 2015-04-20 14:04:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Array.st,v 1.167 2015-04-22 17:27:19 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Array.st,v 1.166 2015-04-20 14:04:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Array.st,v 1.167 2015-04-22 17:27:19 stefan Exp $'
 ! !
+
--- a/Character.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/Character.st	Thu Apr 23 08:04:13 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -324,6 +326,7 @@
     ^ self codePoint:anInteger
 ! !
 
+
 !Character class methodsFor:'accessing untypeable characters'!
 
 controlCharacter:char
@@ -370,6 +373,7 @@
     ^ self codePoint:41
 ! !
 
+
 !Character class methodsFor:'constants'!
 
 backspace
@@ -607,6 +611,7 @@
     "
 ! !
 
+
 !Character methodsFor:'Compatibility-Dolphin'!
 
 isAlphaNumeric
@@ -654,6 +659,7 @@
       or:[ (asciivalue == 247 ) ]]]]]
 ! !
 
+
 !Character methodsFor:'accessing'!
 
 codePoint
@@ -1455,7 +1461,7 @@
     ^ s contents
 
     "
-	'ä' utf8Encoded
+	'ä' utf8Encoded
     "
 ! !
 
@@ -2501,18 +2507,17 @@
 
     "
      $e asNonDiacritical
-     $é asNonDiacritical
-     $ä asNonDiacritical
-     $å asNonDiacritical
+     $é asNonDiacritical
+     $ä asNonDiacritical
+     $Ã¥ asNonDiacritical
     "
 !
 
 isNationalAlphaNumeric
-    "return true, if the receiver is a letter or digit in the
-     current language (Language variable)"
-
-    self isNationalLetter ifTrue:[^ true].
-    ^ self isNationalDigit
+    "return true, if the receiver is a letter or digit.
+     This assumes unicode encoding."
+
+    ^ self isNationalLetter or:[self isNationalDigit]
 !
 
 isNationalDigit
@@ -2525,12 +2530,10 @@
     codePoint := asciivalue.
 
     codePoint <= 16rFF ifTrue:[                "/ u00xx - unicode latin1 page
-	(codePoint between:($0 codePoint) and:($9 codePoint)) ifTrue:[^ true].
-	^ false
+        ^ codePoint between:$0 codePoint and:$9 codePoint.
     ].
 
-    (codePoint between:16rFF10 and:16rFF19) ifTrue:[ ^ true].
-    ^ false.
+    ^ codePoint between:16rFF10 and:16rFF19
 !
 
 isNationalLetter
@@ -3035,9 +3038,10 @@
 !Character class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Character.st,v 1.161 2015-04-20 10:48:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Character.st,v 1.162 2015-04-22 17:38:30 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Character.st,v 1.161 2015-04-20 10:48:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Character.st,v 1.162 2015-04-22 17:38:30 stefan Exp $'
 ! !
+
--- a/CharacterArray.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/CharacterArray.st	Thu Apr 23 08:04:13 2015 +0100
@@ -1612,7 +1612,7 @@
                             "expand with arg itself"
                             arg isText ifTrue:[
                                 out contentsSpecies isText ifFalse:[
-                                    out := (WriteStream on:Text new) nextPutAll:out contents; yourself.
+                                    out := (TextStream ? CharacterWriteStream on:Text new) nextPutAll:out contents; yourself.
                                 ].
                                 out nextPutAll:arg.
                             ] ifFalse:[
@@ -5828,7 +5828,7 @@
 
     |stream|
 
-    stream := (TextStream ? WriteStream) on:(self species new:self size + 20).
+    stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
     self expandPlaceholders:escapeCharacter with:argArrayOrDictionary on:stream.
     ^ stream contents.
 
@@ -6012,7 +6012,7 @@
 
     |stream|
 
-    stream := (TextStream ? WriteStream) on:(self species new:self size + 20).
+    stream := (TextStream ? CharacterWriteStream) on:(self species uninitializedNew:self size + 20).
     self expandPlaceholdersWith:argArrayOrDictionary on:stream.
     ^ stream contents.
 
@@ -6158,7 +6158,7 @@
 
     self hasChangeOfEmphasis ifTrue:[ self error:'emphasis not supported' ].
 
-    out := WriteStream on:(String new:self size-1).
+    out := WriteStream on:(String uninitializedNew:self size-1).
 
     self do:[:ch |
         |cp|
@@ -7393,11 +7393,11 @@
 !CharacterArray class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.582 2015-04-09 11:42:14 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.583 2015-04-22 17:45:10 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.582 2015-04-09 11:42:14 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.583 2015-04-22 17:45:10 stefan Exp $'
 !
 
 version_HG
--- a/CharacterWriteStream.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/CharacterWriteStream.st	Thu Apr 23 08:04:13 2015 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2005 by eXept Software AG
               All Rights Reserved
@@ -72,6 +70,20 @@
 "
 ! !
 
+!CharacterWriteStream class methodsFor:'instance creation'!
+
+new
+    "I know, that I operate on strings"
+
+    ^ self on:(String new:10)
+!
+
+new:count
+    "I know, that I operate on strings"
+
+    ^ self on:(String new:count)
+! !
+
 !CharacterWriteStream methodsFor:'accessing'!
 
 reset
@@ -255,10 +267,10 @@
 !CharacterWriteStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterWriteStream.st,v 1.13 2015-03-14 21:31:57 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterWriteStream.st,v 1.14 2015-04-22 14:05:37 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterWriteStream.st,v 1.13 2015-03-14 21:31:57 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterWriteStream.st,v 1.14 2015-04-22 14:05:37 stefan Exp $'
 ! !
 
--- a/Collection.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/Collection.st	Thu Apr 23 08:04:13 2015 +0100
@@ -339,6 +339,7 @@
     ^ self == Collection
 ! !
 
+
 !Collection methodsFor:'Compatibility-Dolphin'!
 
 identityIncludes:anObject
@@ -4094,7 +4095,7 @@
         s := aStream.
         limit := s position + limit.
     ] ifFalse:[
-        s := WriteStream on:(String uninitializedNew:50).
+        s := CharacterWriteStream new:50.
     ].
 
     self printElementsDo:[:element |
@@ -4119,7 +4120,7 @@
     aStream nextPut:$)
 
     "
-     #(1 2 3 'hello' $a) printOn:Transcript
+     #(1 2 3 'hello' $a $ü) printOn:Transcript
      (Array new:100000) printOn:Transcript
      (Array new:100000) printOn:Stdout          
      (Array new:100000) printString size 
@@ -5748,11 +5749,11 @@
 !Collection class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Collection.st,v 1.362 2015-04-13 14:02:13 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Collection.st,v 1.363 2015-04-22 17:45:38 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Collection.st,v 1.362 2015-04-13 14:02:13 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Collection.st,v 1.363 2015-04-22 17:45:38 stefan Exp $'
 ! !
 
 
--- a/Context.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/Context.st	Thu Apr 23 08:04:13 2015 +0100
@@ -1021,7 +1021,7 @@
     "print the receiver, selector and args of the context
      - used only for MiniDebuggers walkback print"
 
-    self receiverPrintString print. ' ' errorPrint. selector errorPrint.
+    self receiverPrintString errorPrint. ' ' errorPrint. selector errorPrint.
     self size ~~ 0 ifTrue: [
 	' ' errorPrint. self argsDisplayString errorPrint
     ].
@@ -2860,11 +2860,11 @@
 !Context class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.215 2015-04-21 19:40:22 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.216 2015-04-22 12:25:14 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.215 2015-04-21 19:40:22 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Context.st,v 1.216 2015-04-22 12:25:14 cg Exp $'
 !
 
 version_HG
--- a/Date.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/Date.st	Thu Apr 23 08:04:13 2015 +0100
@@ -882,6 +882,7 @@
     ^ self newDay:day month:mon year:yr
 ! !
 
+
 !Date class methodsFor:'change & update'!
 
 update:something with:aParameter from:changedObject
@@ -1696,6 +1697,7 @@
     ^ self leapYear:yearInteger
 ! !
 
+
 !Date class methodsFor:'private'!
 
 dayAbbrevsForLanguage:languageOrNilForDefault
@@ -1869,6 +1871,7 @@
     "
 ! !
 
+
 !Date methodsFor:'Compatibility-ANSI'!
 
 dayOfWeek
@@ -3025,6 +3028,7 @@
 ! !
 
 
+
 !Date methodsFor:'obsolete'!
 
 asAbsoluteTime
@@ -3360,7 +3364,7 @@
 
     |s|
 
-    s := WriteStream on:(String new:20).
+    s := CharacterWriteStream new:20.
     self printOn:s format:aFormatStringOrArray language:languageOrNil.
     ^ s contents.
 
@@ -3471,11 +3475,11 @@
 !Date class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Date.st,v 1.168 2015-03-26 17:06:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Date.st,v 1.169 2015-04-22 17:50:37 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Date.st,v 1.168 2015-03-26 17:06:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Date.st,v 1.169 2015-04-22 17:50:37 stefan Exp $'
 ! !
 
 
--- a/Filename.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/Filename.st	Thu Apr 23 08:04:13 2015 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1992 by Claus Gittinger
               All Rights Reserved
@@ -735,7 +737,7 @@
     "/ fallBack - works on Unix & MSDOS
 
     sep := self separatorString.
-    s := WriteStream on:''.
+    s := CharacterWriteStream new.
     aCollectionOfDirectoryNames do:[:component |
         component ~= sep ifTrue:[
             s nextPutAll:sep; nextPutAll:component
@@ -2075,6 +2077,7 @@
     "Created: 20.6.1997 / 17:01:28 / cg"
 ! !
 
+
 !Filename methodsFor:'enumerating-contents'!
 
 allDirectoriesDo:aBlock
@@ -4037,7 +4040,7 @@
             normalizedPath add:eachPathComponent.
         ]]
     ].
-    pathStream := WriteStream with:nameString.
+    pathStream := CharacterWriteStream with:nameString.
     (nameString notEmpty and:[(nameString endsWith:sepString) not]) ifTrue:[
         pathStream nextPutAll:sepString.
     ].
@@ -4050,7 +4053,7 @@
     ^ pathStream contents.
 
     "
-     '/tmp' asFilename secureConstructString:'foo'   
+     '/tmp' asFilename secureConstructString:'fooÅ '   
      '/tmp' asFilename secureConstructString:'../foo'   
      '/tmp' asFilename secureConstructString:'foo/../bla'   
      '/tmp' asFilename secureConstructString:'foo/./bla'   
@@ -4491,7 +4494,7 @@
      'smalltalk.rc' asFilename mimeTypeFromName     
      'bitmaps/SBrowser.xbm' asFilename mimeTypeFromName    
      '../../rules/stmkmf' asFilename mimeTypeFromName  
-     '/bläh' asFilename mimeTypeFromName               
+     '/bläh' asFilename mimeTypeFromName               
      '/x.zip' asFilename mimeTypeFromName               
      '/x.gz' asFilename mimeTypeFromName               
     "
@@ -4540,7 +4543,7 @@
      'smalltalk.rc' asFilename mimeTypeOfContents      
      'bitmaps/SBrowser.xbm' asFilename mimeTypeOfContents    
      '../../rules/stmkmf' asFilename mimeTypeOfContents 
-     '/bläh' asFilename mimeTypeOfContents              
+     '/bläh' asFilename mimeTypeOfContents              
      'C:\Dokumente und Einstellungen\cg\Favoriten\languages.lnk' asFilename mimeTypeOfContents
      'G:\A\A01.TOP' asFilename mimeTypeOfContents       
     "
@@ -5329,7 +5332,7 @@
      readable directories pathname, and the directory is not empty."
 
     FileStream openErrorSignal
-        handle:[:ex ]
+        handle:[:ex| ]
         do:[
             self directoryContentsDo:[:pathString|^ true].
         ].
@@ -6140,11 +6143,11 @@
 !Filename class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.434 2015-01-21 19:03:50 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.435 2015-04-22 17:59:59 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.434 2015-01-21 19:03:50 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Filename.st,v 1.435 2015-04-22 17:59:59 stefan Exp $'
 ! !
 
 
--- a/Object.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/Object.st	Thu Apr 23 08:04:13 2015 +0100
@@ -5869,6 +5869,9 @@
     "send the two-arg-message aSelector to the receiver"
 
 %{
+#ifdef __SCHTEAM__
+    return context.PERFORM_WITH2(self, aSelector, arg1, arg2);
+#else
     REGISTER OBJ sel = aSelector;
     struct inlineCache *pIlc;
     int hash0;
@@ -5941,6 +5944,7 @@
 	static struct inlineCache ilc2 = __DUMMYILCSELF2(@line+1);
 	RETURN (_SEND2(self, aSelector, nil, &ilc2, arg1, arg2));
     }
+#endif /* not SCHTEAM */
 %}.
     ^ self perform:aSelector withArguments:(Array with:arg1 with:arg2)
 !
@@ -5949,6 +5953,9 @@
     "send the three-arg-message aSelector to the receiver"
 
 %{
+#ifdef __SCHTEAM__
+    return context.PERFORM_WITH3(self, aSelector, arg1, arg2, arg3);
+#else
     struct inlineCache *pIlc;
     static struct inlineCache ilc_0 = __ILCPERF3(@line);
     static struct inlineCache ilc_1 = __ILCPERF3(@line);
@@ -5984,6 +5991,7 @@
 	static struct inlineCache ilc3 = __DUMMYILCSELF3(@line+1);
 	RETURN (_SEND3(self, aSelector, nil, &ilc3, arg1, arg2, arg3));
     }
+#endif /* not SCHTEAM */
 %}.
     ^ self perform:aSelector withArguments:(Array with:arg1 with:arg2 with:arg3)
 
@@ -10268,11 +10276,11 @@
 !Object class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.800 2015-04-21 19:40:51 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.801 2015-04-22 12:24:50 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.800 2015-04-21 19:40:51 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.801 2015-04-22 12:24:50 cg Exp $'
 !
 
 version_HG
--- a/PeekableStream.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/PeekableStream.st	Thu Apr 23 08:04:13 2015 +0100
@@ -558,9 +558,9 @@
 
     | out ch |
 
-    out := WriteStream on: (String uninitializedNew: 1000).
     self atEnd ifTrue: [^ ''].
     self next == terminator ifFalse: [self skip: -1].       "absorb initial terminator"
+    out := WriteStream on:(self contentsSpecies new).
     [(ch := self next) == nil] whileFalse: [
         (ch == terminator) ifTrue: [
             self peek == terminator ifFalse: [
@@ -710,7 +710,9 @@
 nextAlphaNumericWord
     "read the next word (i.e. up to non letter-or-digit).
      Return a string containing those characters.
-     Any leading non-alphaNumeric chars are skipped."
+     Any leading non-alphaNumeric chars are skipped.
+
+     National letters or digits in unicode are not treated as letters."
 
     |s c|
 
@@ -725,7 +727,7 @@
     ] whileFalse.
 
     "second: get the alphanumeric word"
-    s := WriteStream on:(String new:128).
+    s := WriteStream on:(self contentsSpecies new:100).
 
     [
         s nextPut:c.
@@ -740,7 +742,7 @@
 
     ^ s contents.
 
-    "Use UnicodString in the examples, to avoid the optimization in ReadStream for Strings"
+    "Use UnicodeString in the examples, to avoid the optimization in ReadStream for Strings"
 
     "
      |s|
@@ -845,11 +847,11 @@
 !PeekableStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/PeekableStream.st,v 1.54 2015-04-14 11:04:28 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/PeekableStream.st,v 1.55 2015-04-22 18:01:58 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/PeekableStream.st,v 1.54 2015-04-14 11:04:28 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/PeekableStream.st,v 1.55 2015-04-22 18:01:58 stefan Exp $'
 ! !
 
 
--- a/ReadStream.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/ReadStream.st	Thu Apr 23 08:04:13 2015 +0100
@@ -213,41 +213,40 @@
     l = __INST(readLimit);
 
     if (__isNonNilObject(coll) && __bothSmallInteger(p, l)) {
-
-	pos = __intVal(p);
-	if (pos >= 0 && pos < __intVal(l)) {
-	    OBJ cls, ret;
+        pos = __intVal(p);
+        if (pos >= 0 && pos < __intVal(l)) {
+            OBJ cls, ret;
 
-	    cls = __qClass(coll);
-	    if (cls == @global(String)) {
-		if (pos < __stringSize(coll)) {
-		    ch = __stringVal(coll)[pos];
-		    ret = __MKCHARACTER(ch);
-		    __INST(position) = __mkSmallInteger(pos+1);
-		    RETURN ( ret );
-		}
-	    } else if (cls == @global(ByteArray)) {
-		if (pos < __byteArraySize(coll)) {
-		    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
-		    ret = __mkSmallInteger(ch);
-		    __INST(position) = __mkSmallInteger(pos+1);
-		    RETURN ( ret );
-		}
-	    } else if (cls == @global(Unicode16String)) {
-		if (pos < __unicode16StringSize(coll)) {
-		    ch = __Unicode16StringInstPtr(coll)->s_element[pos];
-		    ret = __MKUCHARACTER(ch);
-		    __INST(position) = __mkSmallInteger(pos+1);
-		    RETURN ( ret );
-		}
-	    } else if (cls == @global(Array)) {
-		if (pos < __arraySize(coll)) {
-		    ret = __ArrayInstPtr(coll)->a_element[pos];
-		    __INST(position) = __mkSmallInteger(pos+1);
-		    RETURN ( ret );
-		}
-	    }
-	}
+            cls = __qClass(coll);
+            if (cls == @global(String) || cls == @global(ImmutableString) || cls == @global(Symbol)) {
+                if (pos < __stringSize(coll)) {
+                    ch = __stringVal(coll)[pos];
+                    ret = __MKCHARACTER(ch);
+                    __INST(position) = __mkSmallInteger(pos+1);
+                    RETURN ( ret );
+                }
+            } else if (cls == @global(ByteArray)) {
+                if (pos < __byteArraySize(coll)) {
+                    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
+                    ret = __mkSmallInteger(ch);
+                    __INST(position) = __mkSmallInteger(pos+1);
+                    RETURN ( ret );
+                }
+            } else if (cls == @global(Unicode16String)) {
+                if (pos < __unicode16StringSize(coll)) {
+                    ch = __unicode16StringVal(coll)[pos];
+                    ret = __MKUCHARACTER(ch);
+                    __INST(position) = __mkSmallInteger(pos+1);
+                    RETURN ( ret );
+                }
+            } else if (cls == @global(Array)) {
+                if (pos < __arraySize(coll)) {
+                    ret = __ArrayInstPtr(coll)->a_element[pos];
+                    __INST(position) = __mkSmallInteger(pos+1);
+                    RETURN ( ret );
+                }
+            }
+        }
     }
 %}.
     (position >= readLimit) ifTrue:[^ self pastEndRead].
@@ -386,44 +385,43 @@
     l = __INST(readLimit);
 
     if (__isNonNilObject(coll) && __bothSmallInteger(p, l)) {
-
-	pos = __intVal(p);
-	if (pos >= 0 && pos < __intVal(l)) {
-	    OBJ cls, ret;
+        pos = __intVal(p);
+        if (pos >= 0 && pos < __intVal(l)) {
+            OBJ cls, ret;
 
-	    cls = __qClass(coll);
-	    if (cls == @global(String)) {
-		if (pos < __stringSize(coll)) {
-		    ch = __stringVal(coll)[pos];
-		    ret = __mkSmallInteger(ch);
-		    __INST(position) = __mkSmallInteger(pos+1);
-		    RETURN ( ret );
-		}
-	    } else if (cls == @global(ByteArray)) {
-		if (pos < __byteArraySize(coll)) {
-		    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
-		    ret = __mkSmallInteger(ch);
-		    __INST(position) = __mkSmallInteger(pos+1);
-		    RETURN ( ret );
-		}
-	    } else if (cls == @global(Array)) {
-		if (pos < __arraySize(coll)) {
-		    ret = __ArrayInstPtr(coll)->a_element[pos];
-		    if (!__isSmallInteger(ret) || __intVal(ret) > 255) goto out;
-		    __INST(position) = __mkSmallInteger(pos+1);
-		    RETURN ( ret );
-		}
-	    }
-	}
+            cls = __qClass(coll);
+            if (cls == @global(String) || cls == @global(ImmutableString) || cls == @global(Symbol)) {
+                if (pos < __stringSize(coll)) {
+                    ch = __stringVal(coll)[pos];
+                    ret = __mkSmallInteger(ch);
+                    __INST(position) = __mkSmallInteger(pos+1);
+                    RETURN ( ret );
+                }
+            } else if (cls == @global(ByteArray)) {
+                if (pos < __byteArraySize(coll)) {
+                    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
+                    ret = __mkSmallInteger(ch);
+                    __INST(position) = __mkSmallInteger(pos+1);
+                    RETURN ( ret );
+                }
+            } else if (cls == @global(Array)) {
+                if (pos < __arraySize(coll)) {
+                    ret = __ArrayInstPtr(coll)->a_element[pos];
+                    if (!__isSmallInteger(ret) || __intVal(ret) > 255) goto out;
+                    __INST(position) = __mkSmallInteger(pos+1);
+                    RETURN ( ret );
+                }
+            }
+        }
     }
 out:;
 %}.
     (position >= readLimit) ifTrue:[^ self pastEndRead].
     ret := (collection at:(position + 1)) asInteger.
     ret > 255 ifTrue:[
-	ret := ConversionError
-	    raiseRequestWith:self
-	    errorString:' - #nextByte trying to read a non-byte'.
+        ret := ConversionError
+            raiseRequestWith:self
+            errorString:' - #nextByte trying to read a non-byte'.
     ].
     position := position + 1.
     ^ ret
@@ -510,44 +508,44 @@
     l = __INST(readLimit);
 
     if (__isNonNilObject(coll) && __bothSmallInteger(p, l)) {
-	pos = __intVal(p);
-	if (pos >= 0) {
-	    OBJ cls, ret;
+        pos = __intVal(p);
+        if (pos >= 0) {
+            OBJ cls, ret;
 
-	    if (pos >= __intVal(l)) {
-		RETURN(nil);
-	    }
+            if (pos >= __intVal(l)) {
+                RETURN(nil);
+            }
 
-	    cls = __qClass(coll);
-	    if (cls == @global(String)) {
-		if (pos < __stringSize(coll)) {
-		    ch = __stringVal(coll)[pos];
-		    ret = __MKCHARACTER(ch);
-		    __INST(position) = __mkSmallInteger(pos + 1);
-		    RETURN ( ret );
-		}
-	    } else if (cls == @global(ByteArray)) {
-		if (pos < __byteArraySize(coll)) {
-		    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
-		    ret = __mkSmallInteger(ch);
-		    __INST(position) = __mkSmallInteger(pos + 1);
-		    RETURN ( ret );
-		}
-	    } else if (cls == @global(Unicode16String)) {
-		if (pos < __unicode16StringSize(coll)) {
-		    ch = __Unicode16StringInstPtr(coll)->s_element[pos];
-		    ret = __MKUCHARACTER(ch);
-		    __INST(position) = __mkSmallInteger(pos + 1);
-		    RETURN ( ret );
-		}
-	    } else if (cls == @global(Array)) {
-		if (pos < __arraySize(coll)) {
-		    ret = __ArrayInstPtr(coll)->a_element[pos];
-		    __INST(position) = __mkSmallInteger(pos + 1);
-		    RETURN ( ret );
-		}
-	    }
-	}
+            cls = __qClass(coll);
+            if (cls == @global(String) || cls == @global(ImmutableString) || cls == @global(Symbol)) {
+                if (pos < __stringSize(coll)) {
+                    ch = __stringVal(coll)[pos];
+                    ret = __MKCHARACTER(ch);
+                    __INST(position) = __mkSmallInteger(pos + 1);
+                    RETURN ( ret );
+                }
+            } else if (cls == @global(ByteArray)) {
+                if (pos < __byteArraySize(coll)) {
+                    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
+                    ret = __mkSmallInteger(ch);
+                    __INST(position) = __mkSmallInteger(pos + 1);
+                    RETURN ( ret );
+                }
+            } else if (cls == @global(Unicode16String)) {
+                if (pos < __unicode16StringSize(coll)) {
+                    ch = __unicode16StringVal(coll)[pos];
+                    ret = __MKUCHARACTER(ch);
+                    __INST(position) = __mkSmallInteger(pos + 1);
+                    RETURN ( ret );
+                }
+            } else if (cls == @global(Array)) {
+                if (pos < __arraySize(coll)) {
+                    ret = __ArrayInstPtr(coll)->a_element[pos];
+                    __INST(position) = __mkSmallInteger(pos + 1);
+                    RETURN ( ret );
+                }
+            }
+        }
     }
 %}.
     position := position + 1.
@@ -604,25 +602,30 @@
 
     if (__isNonNilObject(coll) && __bothSmallInteger(p, l)) {
 
-	pos = __intVal(p);
-	if ((pos < __intVal(l)) && (pos >= 0)) {
-	    cls = __qClass(coll);
-	    if (cls == @global(String)) {
-		if (pos < __stringSize(coll)) {
-		    ch = __stringVal(coll)[pos];
-		    RETURN ( __MKCHARACTER(ch) );
-		}
-	    } else if (cls == @global(ByteArray)) {
-		if (pos < __byteArraySize(coll)) {
-		    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
-		    RETURN ( __mkSmallInteger(ch) );
-		}
-	    } else if (cls == @global(Array)) {
-		if (pos < __arraySize(coll)) {
-		    RETURN ( __ArrayInstPtr(coll)->a_element[pos]);
-		}
-	    }
-	}
+        pos = __intVal(p);
+        if ((pos < __intVal(l)) && (pos >= 0)) {
+            cls = __qClass(coll);
+            if (cls == @global(String) || cls == @global(ImmutableString) || cls == @global(Symbol)) {
+                if (pos < __stringSize(coll)) {
+                    ch = __stringVal(coll)[pos];
+                    RETURN ( __MKCHARACTER(ch) );
+                }
+            } else if (cls == @global(ByteArray)) {
+                if (pos < __byteArraySize(coll)) {
+                    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
+                    RETURN ( __mkSmallInteger(ch) );
+                }
+            } else if (cls == @global(Unicode16String)) {
+                if (pos < __unicode16StringSize(coll)) {
+                    ch = __unicode16StringVal(coll)[pos];
+                    RETURN(__MKUCHARACTER(ch));
+                }
+            } else if (cls == @global(Array)) {
+                if (pos < __arraySize(coll)) {
+                    RETURN ( __ArrayInstPtr(coll)->a_element[pos]);
+                }
+            }
+        }
     }
 %}.
     (position >= readLimit) ifTrue:[^ self pastEndRead].
@@ -648,29 +651,34 @@
     l = __INST(readLimit);
 
     if (__isNonNilObject(coll) && __bothSmallInteger(p, l)) {
-
-	pos = __intVal(p);
-	if ((pos < __intVal(l)) && (pos >= 0)) {
-	    cls = __qClass(coll);
-	    if (cls == @global(String)) {
-		if (pos < __stringSize(coll)) {
-		    ch = __stringVal(coll)[pos];
-		    RETURN ( __MKCHARACTER(ch) );
-		}
-		RETURN ( nil );
-	    } else if (cls == @global(ByteArray)) {
-		if (pos < __byteArraySize(coll)) {
-		    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
-		    RETURN ( __mkSmallInteger(ch) );
-		}
-		RETURN ( nil );
-	    } else if (cls == @global(Array)) {
-		if (pos < __arraySize(coll)) {
-		    RETURN ( __ArrayInstPtr(coll)->a_element[pos]);
-		}
-		RETURN ( nil );
-	    }
-	}
+        pos = __intVal(p);
+        if ((pos < __intVal(l)) && (pos >= 0)) {
+            cls = __qClass(coll);
+            if (cls == @global(String) || cls == @global(ImmutableString) || cls == @global(Symbol)) {
+                if (pos < __stringSize(coll)) {
+                    ch = __stringVal(coll)[pos];
+                    RETURN ( __MKCHARACTER(ch) );
+                }
+                RETURN ( nil );
+            } else if (cls == @global(ByteArray)) {
+                if (pos < __byteArraySize(coll)) {
+                    ch = __ByteArrayInstPtr(coll)->ba_element[pos];
+                    RETURN ( __mkSmallInteger(ch) );
+                }
+                RETURN ( nil );
+            } else if (cls == @global(Unicode16String)) {
+                if (pos < __unicode16StringSize(coll)) {
+                    ch = __unicode16StringVal(coll)[pos];
+                    RETURN(__MKUCHARACTER(ch));
+                }
+                RETURN ( nil );
+            } else if (cls == @global(Array)) {
+                if (pos < __arraySize(coll)) {
+                    RETURN ( __ArrayInstPtr(coll)->a_element[pos]);
+                }
+                RETURN ( nil );
+            }
+        }
     }
 %}.
     (position >= readLimit) ifTrue:[^ nil].
@@ -909,10 +917,10 @@
 !ReadStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ReadStream.st,v 1.82 2015-04-07 10:22:50 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ReadStream.st,v 1.83 2015-04-22 16:05:16 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/ReadStream.st,v 1.82 2015-04-07 10:22:50 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ReadStream.st,v 1.83 2015-04-22 16:05:16 stefan Exp $'
 ! !
 
--- a/UserPreferences.st	Wed Apr 22 07:33:07 2015 +0100
+++ b/UserPreferences.st	Thu Apr 23 08:04:13 2015 +0100
@@ -62,57 +62,57 @@
     DefaultPreferences := self new.
 
     Color isNil "Smalltalk isStandAloneApp" ifTrue:[
-        ^ self.
+	^ self.
     ].
 
     #(
-        #useNewChangesBrowser           false
-        #useNewInspector                false
-        #showClockInLauncher            true
-
-        #autoFormatting                 false
-        #syntaxColoring                 true
-        #fullSelectorCheck              false
-
-        #defaultSyntaxColor             (Color black)
-        #defaultSyntaxEmphasis          normal
-
-        #errorColor                     (Color red)
-
-        "/ #commentColor                   (Color 12.5 12.5 100)
-        #commentColor                   (Color 0 50 0)
-        #commentEmphasis                normal
-
-        #methodSelectorEmphasis         bold
-        #selectorEmphasis               bold
-        #unimplementedSelectorColor     (Color red)
-        #unimplementedSelectorEmphasis  normal
-
-        "/ I prefer red-underwave over red identifier ...
-        "/      #badIdentifierColor                 (Color red)
-        #instVarIdentifierColor         (Color 33 0 33)
-
-        "/ I prefer redish background
-        "/      #sideEffectAssignmentColor          (Color 75 0 0)
-        "/ #sideEffectAssignmentBackgroundColor    (Color 100 86 86)
-
-        #jsKeywordEmphasis              bold
-        "/ #jsKeywordColor                 (Color black)
-        #jsKeywordColor                 (Color 33 33 0)
-
-        #controlFlowSelectorColor       (Color 0 0 100)
-        #debugSelectorColor             (Color 80 0 0)
-        #errorRaisingSelectorColor      (Color 80 0 0)
-        "/ #constantColor                  (Color 25 0 0)
-        #constantColor                  (Color 64 8 8)
-
-        #globalIdentifierColor          (Color 67 0 67)
-        #unknownIdentifierColor         (Color 67 0 67)
-
-        #returnColor                    (Color 0 0 100)
-        #returnEmphasis                 bold
+	#useNewChangesBrowser           false
+	#useNewInspector                false
+	#showClockInLauncher            true
+
+	#autoFormatting                 false
+	#syntaxColoring                 true
+	#fullSelectorCheck              false
+
+	#defaultSyntaxColor             (Color black)
+	#defaultSyntaxEmphasis          normal
+
+	#errorColor                     (Color red)
+
+	"/ #commentColor                   (Color 12.5 12.5 100)
+	#commentColor                   (Color 0 50 0)
+	#commentEmphasis                normal
+
+	#methodSelectorEmphasis         bold
+	#selectorEmphasis               bold
+	#unimplementedSelectorColor     (Color red)
+	#unimplementedSelectorEmphasis  normal
+
+	"/ I prefer red-underwave over red identifier ...
+	"/      #badIdentifierColor                 (Color red)
+	#instVarIdentifierColor         (Color 33 0 33)
+
+	"/ I prefer redish background
+	"/      #sideEffectAssignmentColor          (Color 75 0 0)
+	"/ #sideEffectAssignmentBackgroundColor    (Color 100 86 86)
+
+	#jsKeywordEmphasis              bold
+	"/ #jsKeywordColor                 (Color black)
+	#jsKeywordColor                 (Color 33 33 0)
+
+	#controlFlowSelectorColor       (Color 0 0 100)
+	#debugSelectorColor             (Color 80 0 0)
+	#errorRaisingSelectorColor      (Color 80 0 0)
+	"/ #constantColor                  (Color 25 0 0)
+	#constantColor                  (Color 64 8 8)
+
+	#globalIdentifierColor          (Color 67 0 67)
+	#unknownIdentifierColor         (Color 67 0 67)
+
+	#returnColor                    (Color 0 0 100)
+	#returnEmphasis                 bold
      ) pairWiseDo:[:k :v |
-        DefaultPreferences at:k put:(v decodeAsLiteralArray).
+	DefaultPreferences at:k put:(v decodeAsLiteralArray).
     ].
 
     "/ I prefer red-underwave over red identifier ...
@@ -129,8 +129,8 @@
 
 current
     CurrentPreferences isNil ifTrue:[
-        CurrentPreferences := self new.
-        CurrentPreferences flyByHelpSettingChanged.
+	CurrentPreferences := self new.
+	CurrentPreferences flyByHelpSettingChanged.
     ].
     ^ CurrentPreferences.
 
@@ -286,171 +286,171 @@
     "returns the names and keys of syntax color items"
 
     ^#(
-        (
-          'Argument Identifier Color'
-          argumentIdentifierColor
-          argumentIdentifierEmphasis
-        )
-        (
-          'Boolean Constant Color'
-          booleanConstantColor
-          booleanConstantEmphasis
-        )
-        (
-          'Bracket Color'
-          bracketColor
-          bracketEmphasis
-        )
-        (
-          'Class Variable Identifier Color'
-          classVariableIdentifierColor
-          classVariableIdentifierEmphasis
-        )
-        (
-          'Constant Color'
-          constantColor
-          constantEmphasis
-        )
-        (
-          'Control Flow Selector Color'
-          controlFlowSelectorColor
-          controlFlowSelectorEmphasis
-        )
-        (
-          'Comment Color'
-          commentColor
-          commentEmphasis
-        )
-        (
-          'Collection Enumeration Selector Color'
-          collectionEnumerationSelectorColor
-          collectionEnumerationSelectorEmphasis
-        )
-        (
-          'Debug Selector Color'
-          debugSelectorColor
-          debugSelectorEmphasis
-        )
-        (
-          'Default Syntax Color'
-          defaultSyntaxColor
-          defaultSyntaxEmphasis
-        )
-        (
-          'Error Raising Selector Color'
-          errorColor
-          errorEmphasis
-        )
-        (
-          'Global Identifier Color'
-          globalIdentifierColor
-          globalIdentifierEmphasis
-        )
-        (
-          'Global Class Identifier Color'
-          globalClassIdentifierColor
-          globalClassIdentifierEmphasis
-        )
-        (
-          'Here Color'
-          hereColor
-          hereEmphasis
-        )
-        (
-          'Identifier Color'
-          identifierColor
-          identifierEmphasis
-        )
-        (
-          'InstVar Identifier Color'
-          instVarIdentifierColor
-          instVarIdentifierEmphasis
-        )
-        (
-          'Local Identifier Color'
-          localIdentifierColor
-          localIdentifierEmphasis
-        )
-        (
-          'Method Selector Color'
-          methodSelectorColor
-          methodSelectorEmphasis
-        )
-        (
-          'Pool Variable Identifier Color'
-          poolVariableIdentifierColor
-          poolVariableIdentifierEmphasis
-        )
-        (
-          'Return Color'
-          returnColor
-          returnEmphasis
-        )
-        (
-          'Selector Color'
-          selectorColor
-          selectorEmphasis
-        )
-        (
-          'Self Color'
-          selfColor
-          selfEmphasis
-        )
-        (
-          'String Color'
-          stringColor
-          stringEmphasis
-        )
-        (
-          'Super Color'
-          superColor
-          superEmphasis
-        )
-        (
-          'Symbol Color'
-          symbolColor
-          symbolEmphasis
-        )
-        (
-          'This Context Color'
-          thisContextColor
-          thisContextEmphasis
-        )
-        (
-          'Unknown Identifier Color'
-          unknownIdentifierColor
-          unknownIdentifierEmphasis
-        )
-        (
-          'Unimplemented Selector Color'
-          unimplementedSelectorColor
-          unimplementedSelectorEmphasis
-        )
-        (
-          'Side Effect Assignment Color'
-          sideEffectAssignmentColor
-          sideEffectAssignmentColorEmphasis
-        )
-        (
-          'Side Effect Assignment Background Color'
-          sideEffectAssignmentBackgroundColor
-          sideEffectAssignmentBackgroundColorEmphasis
-        )
-        (
-          'Coverage: Reached Color'
-          colorForInstrumentedFullyCoveredCode
-          emphasisForInstrumentedFullyCoveredCode
-        )
-        (
-          'Coverage: Partially Reached Color'
-          colorForInstrumentedPartiallyCoveredCode
-          emphasisForInstrumentedPartiallyCoveredCode
-        )
-        (
-          'Coverage: Unreached Color'
-          colorForInstrumentedNeverCalledCode
-          emphasisForInstrumentedNeverCalledCode
-        )
+	(
+	  'Argument Identifier Color'
+	  argumentIdentifierColor
+	  argumentIdentifierEmphasis
+	)
+	(
+	  'Boolean Constant Color'
+	  booleanConstantColor
+	  booleanConstantEmphasis
+	)
+	(
+	  'Bracket Color'
+	  bracketColor
+	  bracketEmphasis
+	)
+	(
+	  'Class Variable Identifier Color'
+	  classVariableIdentifierColor
+	  classVariableIdentifierEmphasis
+	)
+	(
+	  'Constant Color'
+	  constantColor
+	  constantEmphasis
+	)
+	(
+	  'Control Flow Selector Color'
+	  controlFlowSelectorColor
+	  controlFlowSelectorEmphasis
+	)
+	(
+	  'Comment Color'
+	  commentColor
+	  commentEmphasis
+	)
+	(
+	  'Collection Enumeration Selector Color'
+	  collectionEnumerationSelectorColor
+	  collectionEnumerationSelectorEmphasis
+	)
+	(
+	  'Debug Selector Color'
+	  debugSelectorColor
+	  debugSelectorEmphasis
+	)
+	(
+	  'Default Syntax Color'
+	  defaultSyntaxColor
+	  defaultSyntaxEmphasis
+	)
+	(
+	  'Error Raising Selector Color'
+	  errorColor
+	  errorEmphasis
+	)
+	(
+	  'Global Identifier Color'
+	  globalIdentifierColor
+	  globalIdentifierEmphasis
+	)
+	(
+	  'Global Class Identifier Color'
+	  globalClassIdentifierColor
+	  globalClassIdentifierEmphasis
+	)
+	(
+	  'Here Color'
+	  hereColor
+	  hereEmphasis
+	)
+	(
+	  'Identifier Color'
+	  identifierColor
+	  identifierEmphasis
+	)
+	(
+	  'InstVar Identifier Color'
+	  instVarIdentifierColor
+	  instVarIdentifierEmphasis
+	)
+	(
+	  'Local Identifier Color'
+	  localIdentifierColor
+	  localIdentifierEmphasis
+	)
+	(
+	  'Method Selector Color'
+	  methodSelectorColor
+	  methodSelectorEmphasis
+	)
+	(
+	  'Pool Variable Identifier Color'
+	  poolVariableIdentifierColor
+	  poolVariableIdentifierEmphasis
+	)
+	(
+	  'Return Color'
+	  returnColor
+	  returnEmphasis
+	)
+	(
+	  'Selector Color'
+	  selectorColor
+	  selectorEmphasis
+	)
+	(
+	  'Self Color'
+	  selfColor
+	  selfEmphasis
+	)
+	(
+	  'String Color'
+	  stringColor
+	  stringEmphasis
+	)
+	(
+	  'Super Color'
+	  superColor
+	  superEmphasis
+	)
+	(
+	  'Symbol Color'
+	  symbolColor
+	  symbolEmphasis
+	)
+	(
+	  'This Context Color'
+	  thisContextColor
+	  thisContextEmphasis
+	)
+	(
+	  'Unknown Identifier Color'
+	  unknownIdentifierColor
+	  unknownIdentifierEmphasis
+	)
+	(
+	  'Unimplemented Selector Color'
+	  unimplementedSelectorColor
+	  unimplementedSelectorEmphasis
+	)
+	(
+	  'Side Effect Assignment Color'
+	  sideEffectAssignmentColor
+	  sideEffectAssignmentColorEmphasis
+	)
+	(
+	  'Side Effect Assignment Background Color'
+	  sideEffectAssignmentBackgroundColor
+	  sideEffectAssignmentBackgroundColorEmphasis
+	)
+	(
+	  'Coverage: Reached Color'
+	  colorForInstrumentedFullyCoveredCode
+	  emphasisForInstrumentedFullyCoveredCode
+	)
+	(
+	  'Coverage: Partially Reached Color'
+	  colorForInstrumentedPartiallyCoveredCode
+	  emphasisForInstrumentedPartiallyCoveredCode
+	)
+	(
+	  'Coverage: Unreached Color'
+	  colorForInstrumentedNeverCalledCode
+	  emphasisForInstrumentedNeverCalledCode
+	)
     )
 
     "Modified: / 14-02-2012 / 10:17:46 / cg"
@@ -513,238 +513,238 @@
     screen := Screen current.
 
     (dir := fileName directory) exists ifFalse:[
-        dir recursiveMakeDirectory.
+	dir recursiveMakeDirectory.
     ].
     fileName writingFileDo:[:s|
-        s nextPutLine:'"/ ST/X saved settings';
-          nextPutLine:'"/ DO NOT MODIFY MANUALLY';
-          nextPutLine:'"/ (modifications would be lost with next save-settings)';
-          nextPutLine:'"/';
-          nextPutLine:'"/ this file was automatically generated by the';
-          nextPutLine:'"/ ''save settings'' function of the SettingsDialog';
-          nextPutLine:'"/'.
-        s cr.
-
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ saved by ' , OperatingSystem getLoginName , '@' , OperatingSystem getHostName , ' at ' , Timestamp now printString.
-        s nextPutLine:'"/'.
-        s cr.
-
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ Display settings:'.
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ only restore the display settings, if on the same Display ...'.
-        s nextPutLine:'Display notNil ifTrue:['.
-        s nextPutLine:' Display displayName = ' , (screen displayName storeString) , ' ifTrue:['.
-          screen fixColors notNil ifTrue:[
-            s nextPutLine:'  Image flushDeviceImages.'.
-            s nextPutLine:'  Color colorAllocationFailSignal catch:['.
-            s nextPutLine:'    Color getColorsRed:6 green:6 blue:4 on:Display'.
-            s nextPutLine:'  ].'.
-          ] ifFalse:[
-            s nextPutLine:'  Display releaseFixColors.'.
-          ].
-          s nextPutLine:'  Display hasColors: ' , (screen hasColors storeString) , '.'.
-          s nextPutLine:'  Display widthInMillimeter: ' , (screen widthInMillimeter storeString) , '.'.
-          s nextPutLine:'  Display heightInMillimeter: ' , (screen heightInMillimeter storeString) , '.'.
-          s nextPutLine:'  Display supportsDeepIcons: ' , (screen supportsDeepIcons storeString) , '.'.
-          s nextPutLine:'  Image ditherAlgorithm: ' , (Image ditherAlgorithm storeString) , '.'.
-          s nextPutLine:'  View defaultStyle:' , View defaultStyle storeString , '.'.
-        s nextPutLine:' ].'.
-        s nextPutLine:'].'.
-        s cr.
-
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ Parser/Compiler settings:'.
-        s nextPutLine:'"/'.
-        s nextPutLine:'ParserFlags warnSTXSpecials: ' , (ParserFlags warnSTXSpecials storeString) , '.';
-          nextPutLine:'ParserFlags warnings: ' , (ParserFlags warnings storeString) , '.';
-          nextPutLine:'ParserFlags warnUnderscoreInIdentifier: ' , (ParserFlags warnUnderscoreInIdentifier storeString) , '.';
-          nextPutLine:'ParserFlags warnOldStyleAssignment: ' , (ParserFlags warnOldStyleAssignment storeString) , '.';
-          nextPutLine:'ParserFlags warnCommonMistakes: ' , (ParserFlags warnCommonMistakes storeString) , '.';
-          nextPutLine:'ParserFlags warnPossibleIncompatibilities: ' , (ParserFlags warnPossibleIncompatibilities storeString) , '.';
-          nextPutLine:'ParserFlags allowUnderscoreInIdentifier: ' , (ParserFlags allowUnderscoreInIdentifier storeString) , '.';
-          nextPutLine:'ParserFlags allowSqueakExtensions: ' , (ParserFlags allowSqueakExtensions storeString) , '.';
-          nextPutLine:'ParserFlags allowDolphinExtensions: ' , (ParserFlags allowDolphinExtensions storeString) , '.';
-          nextPutLine:'ParserFlags allowQualifiedNames: ' , (ParserFlags allowQualifiedNames storeString) , '.';
-          nextPutLine:'ParserFlags arraysAreImmutable: ' , (ParserFlags arraysAreImmutable storeString) , '.';
-          nextPutLine:'ParserFlags lineNumberInfo: ' , (ParserFlags lineNumberInfo storeString) , '.';
-
-          nextPutLine:'Compiler foldConstants: ' , (Compiler foldConstants storeString) , '.';
-          nextPutLine:'ParserFlags stcCompilation: ' , (ParserFlags stcCompilation storeString) , '.';
-          nextPutLine:'OperatingSystem getOSType = ' , (OperatingSystem getOSType storeString) , ' ifTrue:[';
-          nextPutLine:'  ParserFlags stcCompilationIncludes: ' , (ParserFlags stcCompilationIncludes storeString) , '.';
-          nextPutLine:'  ParserFlags stcCompilationDefines: ' , (ParserFlags stcCompilationDefines storeString) , '.';
-          nextPutLine:'  ParserFlags stcCompilationOptions: ' , (ParserFlags stcCompilationOptions storeString) , '.';
-          nextPutLine:'  ' , (ParserFlags stcModulePath storeString) , ' asFilename exists ifTrue:[';
-          nextPutLine:'    ParserFlags stcModulePath: ' , (ParserFlags stcModulePath storeString) , '.';
-          nextPutLine:'  ].';
-          nextPutLine:'  ParserFlags stcPath: ' , (ParserFlags stcPath storeString) , '.';
-          nextPutLine:'  ParserFlags ccCompilationOptions: ' , (ParserFlags ccCompilationOptions storeString) , '.';
-          nextPutLine:'  ParserFlags ccPath: ' , (ParserFlags ccPath storeString) , '.';
-          nextPutLine:'  ParserFlags linkArgs: ' , (ParserFlags linkArgs storeString) , '.';
-          nextPutLine:'  ParserFlags linkSharedArgs: ' , (ParserFlags linkSharedArgs storeString) , '.';
-          nextPutLine:'  ParserFlags linkCommand: ' , (ParserFlags linkCommand storeString) , '.';
-          nextPutLine:'  ParserFlags makeCommand: ' , (ParserFlags makeCommand storeString) , '.';
-          nextPutLine:'  ParserFlags libPath: ' , (ParserFlags libPath storeString) , '.';
-          nextPutLine:'  ParserFlags searchedLibraries: ' , (ParserFlags searchedLibraries storeString) , '.';
-          nextPutLine:'].';
-
-          nextPutLine:'ObjectMemory justInTimeCompilation: ' , (ObjectMemory justInTimeCompilation storeString) , '.';
-          nextPutLine:'ObjectMemory fullSingleStepSupport: ' , (ObjectMemory fullSingleStepSupport storeString) , '.'.
-
-        HistoryManager notNil ifTrue:[
-            HistoryManager isActive ifTrue:[
-                s nextPutLine:'HistoryManager notNil ifTrue:[HistoryManager activate].'.
-                s nextPutLine:'HistoryManager notNil ifTrue:[HistoryManager fullHistoryUpdate:' , HistoryManager fullHistoryUpdate storeString , '].'.
-            ] ifFalse:[
-                s nextPutLine:'HistoryManager notNil ifTrue:[HistoryManager deactivate].'.
-            ].
-        ].
-
-        s nextPutLine:'Class catchMethodRedefinitions: ' , (Class catchMethodRedefinitions storeString) , '.'.
-        s nextPutLine:'ClassCategoryReader sourceMode: ' , (ClassCategoryReader sourceMode storeString) , '.'.
-
-        s cr.
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ Info & Debug Messages:'.
-        s nextPutLine:'"/'.
-        s nextPutLine:'Smalltalk hasNoConsole ifFalse:[ ObjectMemory infoPrinting: ' , (ObjectMemory infoPrinting storeString) , '].';
-          nextPutLine:'ObjectMemory debugPrinting: ' , (ObjectMemory debugPrinting storeString) , '.';
-          nextPutLine:'Smalltalk hasNoConsole ifFalse:[ Object infoPrinting: ' , (Object infoPrinting storeString) , '].';
-          nextPutLine:'DeviceWorkstation errorPrinting: ' , (DeviceWorkstation errorPrinting storeString) , '.'.
+	s nextPutLine:'"/ ST/X saved settings';
+	  nextPutLine:'"/ DO NOT MODIFY MANUALLY';
+	  nextPutLine:'"/ (modifications would be lost with next save-settings)';
+	  nextPutLine:'"/';
+	  nextPutLine:'"/ this file was automatically generated by the';
+	  nextPutLine:'"/ ''save settings'' function of the SettingsDialog';
+	  nextPutLine:'"/'.
+	s cr.
+
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ saved by ' , OperatingSystem getLoginName , '@' , OperatingSystem getHostName , ' at ' , Timestamp now printString.
+	s nextPutLine:'"/'.
+	s cr.
+
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ Display settings:'.
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ only restore the display settings, if on the same Display ...'.
+	s nextPutLine:'Display notNil ifTrue:['.
+	s nextPutLine:' Display displayName = ' , (screen displayName storeString) , ' ifTrue:['.
+	  screen fixColors notNil ifTrue:[
+	    s nextPutLine:'  Image flushDeviceImages.'.
+	    s nextPutLine:'  Color colorAllocationFailSignal catch:['.
+	    s nextPutLine:'    Color getColorsRed:6 green:6 blue:4 on:Display'.
+	    s nextPutLine:'  ].'.
+	  ] ifFalse:[
+	    s nextPutLine:'  Display releaseFixColors.'.
+	  ].
+	  s nextPutLine:'  Display hasColors: ' , (screen hasColors storeString) , '.'.
+	  s nextPutLine:'  Display widthInMillimeter: ' , (screen widthInMillimeter storeString) , '.'.
+	  s nextPutLine:'  Display heightInMillimeter: ' , (screen heightInMillimeter storeString) , '.'.
+	  s nextPutLine:'  Display supportsDeepIcons: ' , (screen supportsDeepIcons storeString) , '.'.
+	  s nextPutLine:'  Image ditherAlgorithm: ' , (Image ditherAlgorithm storeString) , '.'.
+	  s nextPutLine:'  View defaultStyle:' , View defaultStyle storeString , '.'.
+	s nextPutLine:' ].'.
+	s nextPutLine:'].'.
+	s cr.
+
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ Parser/Compiler settings:'.
+	s nextPutLine:'"/'.
+	s nextPutLine:'ParserFlags warnSTXSpecials: ' , (ParserFlags warnSTXSpecials storeString) , '.';
+	  nextPutLine:'ParserFlags warnings: ' , (ParserFlags warnings storeString) , '.';
+	  nextPutLine:'ParserFlags warnUnderscoreInIdentifier: ' , (ParserFlags warnUnderscoreInIdentifier storeString) , '.';
+	  nextPutLine:'ParserFlags warnOldStyleAssignment: ' , (ParserFlags warnOldStyleAssignment storeString) , '.';
+	  nextPutLine:'ParserFlags warnCommonMistakes: ' , (ParserFlags warnCommonMistakes storeString) , '.';
+	  nextPutLine:'ParserFlags warnPossibleIncompatibilities: ' , (ParserFlags warnPossibleIncompatibilities storeString) , '.';
+	  nextPutLine:'ParserFlags allowUnderscoreInIdentifier: ' , (ParserFlags allowUnderscoreInIdentifier storeString) , '.';
+	  nextPutLine:'ParserFlags allowSqueakExtensions: ' , (ParserFlags allowSqueakExtensions storeString) , '.';
+	  nextPutLine:'ParserFlags allowDolphinExtensions: ' , (ParserFlags allowDolphinExtensions storeString) , '.';
+	  nextPutLine:'ParserFlags allowQualifiedNames: ' , (ParserFlags allowQualifiedNames storeString) , '.';
+	  nextPutLine:'ParserFlags arraysAreImmutable: ' , (ParserFlags arraysAreImmutable storeString) , '.';
+	  nextPutLine:'ParserFlags lineNumberInfo: ' , (ParserFlags lineNumberInfo storeString) , '.';
+
+	  nextPutLine:'Compiler foldConstants: ' , (Compiler foldConstants storeString) , '.';
+	  nextPutLine:'ParserFlags stcCompilation: ' , (ParserFlags stcCompilation storeString) , '.';
+	  nextPutLine:'OperatingSystem getOSType = ' , (OperatingSystem getOSType storeString) , ' ifTrue:[';
+	  nextPutLine:'  ParserFlags stcCompilationIncludes: ' , (ParserFlags stcCompilationIncludes storeString) , '.';
+	  nextPutLine:'  ParserFlags stcCompilationDefines: ' , (ParserFlags stcCompilationDefines storeString) , '.';
+	  nextPutLine:'  ParserFlags stcCompilationOptions: ' , (ParserFlags stcCompilationOptions storeString) , '.';
+	  nextPutLine:'  ' , (ParserFlags stcModulePath storeString) , ' asFilename exists ifTrue:[';
+	  nextPutLine:'    ParserFlags stcModulePath: ' , (ParserFlags stcModulePath storeString) , '.';
+	  nextPutLine:'  ].';
+	  nextPutLine:'  ParserFlags stcPath: ' , (ParserFlags stcPath storeString) , '.';
+	  nextPutLine:'  ParserFlags ccCompilationOptions: ' , (ParserFlags ccCompilationOptions storeString) , '.';
+	  nextPutLine:'  ParserFlags ccPath: ' , (ParserFlags ccPath storeString) , '.';
+	  nextPutLine:'  ParserFlags linkArgs: ' , (ParserFlags linkArgs storeString) , '.';
+	  nextPutLine:'  ParserFlags linkSharedArgs: ' , (ParserFlags linkSharedArgs storeString) , '.';
+	  nextPutLine:'  ParserFlags linkCommand: ' , (ParserFlags linkCommand storeString) , '.';
+	  nextPutLine:'  ParserFlags makeCommand: ' , (ParserFlags makeCommand storeString) , '.';
+	  nextPutLine:'  ParserFlags libPath: ' , (ParserFlags libPath storeString) , '.';
+	  nextPutLine:'  ParserFlags searchedLibraries: ' , (ParserFlags searchedLibraries storeString) , '.';
+	  nextPutLine:'].';
+
+	  nextPutLine:'ObjectMemory justInTimeCompilation: ' , (ObjectMemory justInTimeCompilation storeString) , '.';
+	  nextPutLine:'ObjectMemory fullSingleStepSupport: ' , (ObjectMemory fullSingleStepSupport storeString) , '.'.
+
+	HistoryManager notNil ifTrue:[
+	    HistoryManager isActive ifTrue:[
+		s nextPutLine:'HistoryManager notNil ifTrue:[HistoryManager activate].'.
+		s nextPutLine:'HistoryManager notNil ifTrue:[HistoryManager fullHistoryUpdate:' , HistoryManager fullHistoryUpdate storeString , '].'.
+	    ] ifFalse:[
+		s nextPutLine:'HistoryManager notNil ifTrue:[HistoryManager deactivate].'.
+	    ].
+	].
+
+	s nextPutLine:'Class catchMethodRedefinitions: ' , (Class catchMethodRedefinitions storeString) , '.'.
+	s nextPutLine:'ClassCategoryReader sourceMode: ' , (ClassCategoryReader sourceMode storeString) , '.'.
+
+	s cr.
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ Info & Debug Messages:'.
+	s nextPutLine:'"/'.
+	s nextPutLine:'Smalltalk hasNoConsole ifFalse:[ ObjectMemory infoPrinting: ' , (ObjectMemory infoPrinting storeString) , '].';
+	  nextPutLine:'ObjectMemory debugPrinting: ' , (ObjectMemory debugPrinting storeString) , '.';
+	  nextPutLine:'Smalltalk hasNoConsole ifFalse:[ Object infoPrinting: ' , (Object infoPrinting storeString) , '].';
+	  nextPutLine:'DeviceWorkstation errorPrinting: ' , (DeviceWorkstation errorPrinting storeString) , '.'.
 
     "/    FlyByHelp isActive ifTrue:[
     "/        s nextPutLine:'FlyByHelp start.'
     "/    ].
 
-        s cr.
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ Edit settings:'.
-        s nextPutLine:'"/'.
-        "/ s nextPutLine:'EditTextView st80Mode: ' , (EditTextView st80Mode storeString) , '.'.
-        "/ s nextPutLine:'TextView st80SelectMode: ' , (TextView st80SelectMode storeString) , '.'.
-        s nextPutLine:'UserPreferences current syntaxColoring: ' , (userPrefs syntaxColoring storeString) , '.'.
-        (ListView userDefaultTabPositions = ListView tab4Positions) ifTrue:[
-            s nextPutLine:'ListView userDefaultTabPositions:(ListView tab4Positions).'.
-        ] ifFalse:[
-            s nextPutLine:'ListView userDefaultTabPositions:(ListView tab8Positions).'.
-        ].
-
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ User preference values:'.
-        s nextPutLine:'"/'.
-        userPrefs keysAndValuesDo:[:k :v |
-            |putSelector|
-
-            putSelector := (k , ':') asSymbolIfInterned.
-            (UserPreferences includesSelector:putSelector) ifTrue:[
-                s nextPutAll:'UserPreferences current ';
-                  nextPutAll:putSelector.
-            ] ifFalse:[
-                s nextPutAll:'UserPreferences current at:'.
-                k storeOn:s.
-                s nextPutAll:' put:'.
-            ].
-            v storeOn:s.
-            s nextPut:$.; cr.
-        ].
-
-        s cr.
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ GC settings:'.
-        s nextPutLine:'"/'.
-        s nextPutLine:'ObjectMemory newSpaceSize: ' , (ObjectMemory newSpaceSize storeString) , '.';
-          nextPutLine:'ObjectMemory dynamicCodeGCTrigger: ' , (ObjectMemory dynamicCodeGCTrigger storeString) , '.';
-          nextPutLine:'ObjectMemory freeSpaceGCAmount: ' , (ObjectMemory freeSpaceGCAmount storeString) , '.';
-          nextPutLine:'ObjectMemory freeSpaceGCLimit: ' , (ObjectMemory freeSpaceGCLimit storeString) , '.';
-          nextPutLine:'ObjectMemory incrementalGCLimit: ' , (ObjectMemory incrementalGCLimit storeString) , '.';
-          nextPutLine:'ObjectMemory oldSpaceCompressLimit: ' , (ObjectMemory oldSpaceCompressLimit storeString) , '.';
-          nextPutLine:'ObjectMemory oldSpaceIncrement: ' , (ObjectMemory oldSpaceIncrement storeString) , '.'.
-
-        s cr.
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ Misc settings:'.
-        s nextPutLine:'"/'.
-        s nextPutLine:'Class keepMethodHistory: ' , (Class methodHistory notNil storeString) , '.';
-          nextPutLine:'Smalltalk logDoits: ' , (Smalltalk logDoits storeString) , '.';
-          nextPutLine:'Autoload compileLazy: ' , (Autoload compileLazy storeString) , '.';
-          nextPutLine:'Smalltalk loadBinaries: ' , (Smalltalk loadBinaries storeString) , '.';
-          nextPutLine:'StandardSystemView includeHostNameInLabel: ' , (StandardSystemView includeHostNameInLabel storeString) , '.';
-
-          "/ claus - I dont think its a good idea to save those ...
+	s cr.
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ Edit settings:'.
+	s nextPutLine:'"/'.
+	"/ s nextPutLine:'EditTextView st80Mode: ' , (EditTextView st80Mode storeString) , '.'.
+	"/ s nextPutLine:'TextView st80SelectMode: ' , (TextView st80SelectMode storeString) , '.'.
+	s nextPutLine:'UserPreferences current syntaxColoring: ' , (userPrefs syntaxColoring storeString) , '.'.
+	(ListView userDefaultTabPositions = ListView tab4Positions) ifTrue:[
+	    s nextPutLine:'ListView userDefaultTabPositions:(ListView tab4Positions).'.
+	] ifFalse:[
+	    s nextPutLine:'ListView userDefaultTabPositions:(ListView tab8Positions).'.
+	].
+
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ User preference values:'.
+	s nextPutLine:'"/'.
+	userPrefs keysAndValuesDo:[:k :v |
+	    |putSelector|
+
+	    putSelector := (k , ':') asSymbolIfInterned.
+	    (UserPreferences includesSelector:putSelector) ifTrue:[
+		s nextPutAll:'UserPreferences current ';
+		  nextPutAll:putSelector.
+	    ] ifFalse:[
+		s nextPutAll:'UserPreferences current at:'.
+		k storeOn:s.
+		s nextPutAll:' put:'.
+	    ].
+	    v storeOn:s.
+	    s nextPut:$.; cr.
+	].
+
+	s cr.
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ GC settings:'.
+	s nextPutLine:'"/'.
+	s nextPutLine:'ObjectMemory newSpaceSize: ' , (ObjectMemory newSpaceSize storeString) , '.';
+	  nextPutLine:'ObjectMemory dynamicCodeGCTrigger: ' , (ObjectMemory dynamicCodeGCTrigger storeString) , '.';
+	  nextPutLine:'ObjectMemory freeSpaceGCAmount: ' , (ObjectMemory freeSpaceGCAmount storeString) , '.';
+	  nextPutLine:'ObjectMemory freeSpaceGCLimit: ' , (ObjectMemory freeSpaceGCLimit storeString) , '.';
+	  nextPutLine:'ObjectMemory incrementalGCLimit: ' , (ObjectMemory incrementalGCLimit storeString) , '.';
+	  nextPutLine:'ObjectMemory oldSpaceCompressLimit: ' , (ObjectMemory oldSpaceCompressLimit storeString) , '.';
+	  nextPutLine:'ObjectMemory oldSpaceIncrement: ' , (ObjectMemory oldSpaceIncrement storeString) , '.'.
+
+	s cr.
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ Misc settings:'.
+	s nextPutLine:'"/'.
+	s nextPutLine:'Class keepMethodHistory: ' , (Class methodHistory notNil storeString) , '.';
+	  nextPutLine:'Smalltalk logDoits: ' , (Smalltalk logDoits storeString) , '.';
+	  nextPutLine:'Autoload compileLazy: ' , (Autoload compileLazy storeString) , '.';
+	  nextPutLine:'Smalltalk loadBinaries: ' , (Smalltalk loadBinaries storeString) , '.';
+	  nextPutLine:'StandardSystemView includeHostNameInLabel: ' , (StandardSystemView includeHostNameInLabel storeString) , '.';
+
+	  "/ claus - I dont think its a good idea to save those ...
     "/      nextPutLine:'"/ Class updateChanges: ' , (Class updatingChanges storeString) , '.';
     "/      nextPutLine:'"/ ObjectMemory nameForChanges: ' , (ObjectMemory nameForChanges storeString) , '.';
 
-          nextPutLine:'StandardSystemView returnFocusWhenClosingModalBoxes: ' , (StandardSystemView returnFocusWhenClosingModalBoxes storeString) , '.';
-          nextPutLine:'StandardSystemView takeFocusWhenMapped: ' , (StandardSystemView takeFocusWhenMapped storeString) , '.';
-          nextPutLine:'Display notNil ifTrue:[';
-          nextPutLine:' Display activateOnClick: ' , ((screen activateOnClick:nil) storeString) , '.';
-          nextPutLine:'].';
-          nextPutLine:'MenuView showAcceleratorKeys: ' , (MenuView showAcceleratorKeys storeString) , '.';
-          nextPutLine:'Class tryLocalSourceFirst: ' , (Class tryLocalSourceFirst storeString) , '.'.
-        (NoHandlerError emergencyHandler == AbstractLauncherApplication notifyingEmergencyHandler) ifTrue:[
-            s nextPutLine:'NoHandlerError emergencyHandler:(AbstractLauncherApplication notifyingEmergencyHandler).'.
-        ].
-        Processor isTimeSlicing ifTrue:[
-            s nextPutLine:'Processor startTimeSlicing.'.
-            s nextPutLine:('Processor supportDynamicPriorities:' , (Processor supportDynamicPriorities ? false) storeString , '.').
-        ] ifFalse:[
-            s nextPutLine:'Processor stopTimeSlicing.'.
-        ].
-
-        s cr.
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ Printer settings:'.
-        s nextPutLine:'"/'.
-        Printer notNil ifTrue:[
-            s nextPutLine:'Printer := ' , (Printer name) , '.'.
-            Printer supportsPrintingToCommand ifTrue:[
-                s nextPutLine:'Printer printCommand: ' , (Printer printCommand storeString) , '.'.
-            ].
-            Printer supportsPageSizes ifTrue:[
-                s nextPutLine:'Printer pageFormat: ' , (Printer pageFormat storeString) , '.'.
-                s nextPutLine:'Printer landscape: ' , (Printer landscape storeString) , '.'.
-            ].
-            Printer supportsMargins ifTrue:[
-                s nextPutLine:'Printer topMargin: ' , (Printer topMargin storeString) , '.'.
-                s nextPutLine:'Printer leftMargin: ' , (Printer leftMargin storeString) , '.'.
-                s nextPutLine:'Printer rightMargin: ' , (Printer rightMargin storeString) , '.'.
-                s nextPutLine:'Printer bottomMargin: ' , (Printer bottomMargin storeString) , '.'.
-            ].
-            Printer supportsPostscript ifTrue:[
-                s nextPutLine:'Printer supportsColor: ' , (Printer supportsColor storeString) , '.'.
-            ].
-        ].
-        s cr.
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ Font settings:'.
-        s nextPutLine:'"/ (only restored, if image is restarted on the same display)'.
-        s nextPutLine:'"/'.
-        s nextPutLine:'Display notNil ifTrue:['.
-        s nextPutLine:' Display displayName = ' , (screen displayName storeString) , ' ifTrue:['.
-        {
-            SimpleView . Label . CheckBox . CheckLabel . Button . Toggle .
-            SelectionInListView . MenuView . MenuPanel . NoteBookView . PullDownMenu .
-            TextView . EditTextView . CodeView
-        } do:[:cls |
-            s nextPutLine:'  ',cls name,' defaultFont: ' , (cls defaultFont storeString) , '.'.
-        ].
-        s nextPutLine:' ].'.
-        s nextPutLine:'].'.
-
-        s cr.
-        s nextPutLine:'"/'.
-        s nextPutLine:'"/ SourceCodeManager settings:'.
-        s nextPutLine:'"/ (repositories are networked nowadays, so the settings are host independent)'.
-        s nextPutLine:'"/'.
-        s nextPutLine:'Class tryLocalSourceFirst:' , Class tryLocalSourceFirst storeString , '.'.
-        s nextPutLine:'AbstractSourceCodeManager notNil ifTrue:[AbstractSourceCodeManager cacheDirectoryName:' , AbstractSourceCodeManager cacheDirectoryName storeString , '].'.
-
-        AbstractSourceCodeManager availableManagers do:[:eachManager |
-            eachManager savePreferencesOn:s
-        ].
-        s syncData.
+	  nextPutLine:'StandardSystemView returnFocusWhenClosingModalBoxes: ' , (StandardSystemView returnFocusWhenClosingModalBoxes storeString) , '.';
+	  nextPutLine:'StandardSystemView takeFocusWhenMapped: ' , (StandardSystemView takeFocusWhenMapped storeString) , '.';
+	  nextPutLine:'Display notNil ifTrue:[';
+	  nextPutLine:' Display activateOnClick: ' , ((screen activateOnClick:nil) storeString) , '.';
+	  nextPutLine:'].';
+	  nextPutLine:'MenuView showAcceleratorKeys: ' , (MenuView showAcceleratorKeys storeString) , '.';
+	  nextPutLine:'Class tryLocalSourceFirst: ' , (Class tryLocalSourceFirst storeString) , '.'.
+	(NoHandlerError emergencyHandler == AbstractLauncherApplication notifyingEmergencyHandler) ifTrue:[
+	    s nextPutLine:'NoHandlerError emergencyHandler:(AbstractLauncherApplication notifyingEmergencyHandler).'.
+	].
+	Processor isTimeSlicing ifTrue:[
+	    s nextPutLine:'Processor startTimeSlicing.'.
+	    s nextPutLine:('Processor supportDynamicPriorities:' , (Processor supportDynamicPriorities ? false) storeString , '.').
+	] ifFalse:[
+	    s nextPutLine:'Processor stopTimeSlicing.'.
+	].
+
+	s cr.
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ Printer settings:'.
+	s nextPutLine:'"/'.
+	Printer notNil ifTrue:[
+	    s nextPutLine:'Printer := ' , (Printer name) , '.'.
+	    Printer supportsPrintingToCommand ifTrue:[
+		s nextPutLine:'Printer printCommand: ' , (Printer printCommand storeString) , '.'.
+	    ].
+	    Printer supportsPageSizes ifTrue:[
+		s nextPutLine:'Printer pageFormat: ' , (Printer pageFormat storeString) , '.'.
+		s nextPutLine:'Printer landscape: ' , (Printer landscape storeString) , '.'.
+	    ].
+	    Printer supportsMargins ifTrue:[
+		s nextPutLine:'Printer topMargin: ' , (Printer topMargin storeString) , '.'.
+		s nextPutLine:'Printer leftMargin: ' , (Printer leftMargin storeString) , '.'.
+		s nextPutLine:'Printer rightMargin: ' , (Printer rightMargin storeString) , '.'.
+		s nextPutLine:'Printer bottomMargin: ' , (Printer bottomMargin storeString) , '.'.
+	    ].
+	    Printer supportsPostscript ifTrue:[
+		s nextPutLine:'Printer supportsColor: ' , (Printer supportsColor storeString) , '.'.
+	    ].
+	].
+	s cr.
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ Font settings:'.
+	s nextPutLine:'"/ (only restored, if image is restarted on the same display)'.
+	s nextPutLine:'"/'.
+	s nextPutLine:'Display notNil ifTrue:['.
+	s nextPutLine:' Display displayName = ' , (screen displayName storeString) , ' ifTrue:['.
+	{
+	    SimpleView . Label . CheckBox . CheckLabel . Button . Toggle .
+	    SelectionInListView . MenuView . MenuPanel . NoteBookView . PullDownMenu .
+	    TextView . EditTextView . CodeView
+	} do:[:cls |
+	    s nextPutLine:'  ',cls name,' defaultFont: ' , (cls defaultFont storeString) , '.'.
+	].
+	s nextPutLine:' ].'.
+	s nextPutLine:'].'.
+
+	s cr.
+	s nextPutLine:'"/'.
+	s nextPutLine:'"/ SourceCodeManager settings:'.
+	s nextPutLine:'"/ (repositories are networked nowadays, so the settings are host independent)'.
+	s nextPutLine:'"/'.
+	s nextPutLine:'Class tryLocalSourceFirst:' , Class tryLocalSourceFirst storeString , '.'.
+	s nextPutLine:'AbstractSourceCodeManager notNil ifTrue:[AbstractSourceCodeManager cacheDirectoryName:' , AbstractSourceCodeManager cacheDirectoryName storeString , '].'.
+
+	AbstractSourceCodeManager availableManagers do:[:eachManager |
+	    eachManager savePreferencesOn:s
+	].
+	s syncData.
     ].
 
     "
@@ -765,15 +765,15 @@
 
 at:key ifAbsent:exceptionValue
     ^ super
-        at:key asSymbol
-        ifAbsent:[
-            "/ Look to DefaultPreferences first...
-            (DefaultPreferences notNil and:[self ~~ DefaultPreferences]) ifTrue:[
-                DefaultPreferences at:key ifAbsent:exceptionValue
-            ] ifFalse:[
-                exceptionValue value
-            ]
-        ].
+	at:key asSymbol
+	ifAbsent:[
+	    "/ Look to DefaultPreferences first...
+	    (DefaultPreferences notNil and:[self ~~ DefaultPreferences]) ifTrue:[
+		DefaultPreferences at:key ifAbsent:exceptionValue
+	    ] ifFalse:[
+		exceptionValue value
+	    ]
+	].
 
     "Created: / 15-01-2012 / 14:27:21 / cg"
     "Modified (format): / 05-02-2015 / 07:10:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -789,34 +789,34 @@
 "/    ].
 
     value == true ifTrue:[
-        key == #useNewVersionDiffBrowser ifTrue:[
-            classNameToCheck := #'VersionDiffBrowser'.
-        ].
-        key == #useNewChangesBrowser ifTrue:[
-            classNameToCheck := #'NewChangesBrowser'.
-        ].
-        key == #useNewFileBrowser ifTrue:[
-            classNameToCheck := #'FileBrowserV2'.
-        ].
-        key == #useNewSystemBrowser ifTrue:[
-            classNameToCheck := #'Tools::NewSystemBrowser'.
-        ].
-        key == #useNewInspector ifTrue:[
-            classNameToCheck := #'NewInspector::NewInspectorView'.
-        ].
+	key == #useNewVersionDiffBrowser ifTrue:[
+	    classNameToCheck := #'VersionDiffBrowser'.
+	].
+	key == #useNewChangesBrowser ifTrue:[
+	    classNameToCheck := #'NewChangesBrowser'.
+	].
+	key == #useNewFileBrowser ifTrue:[
+	    classNameToCheck := #'FileBrowserV2'.
+	].
+	key == #useNewSystemBrowser ifTrue:[
+	    classNameToCheck := #'Tools::NewSystemBrowser'.
+	].
+	key == #useNewInspector ifTrue:[
+	    classNameToCheck := #'NewInspector::NewInspectorView'.
+	].
     ].
 
     classNameToCheck notNil ifTrue:[
-        classToCheck := Smalltalk at:classNameToCheck.
-        classToCheck isNil ifTrue:[
-            ('UserPreferences [warning]: no class ' , classNameToCheck , ' class in system.') errorPrintCR.
-        ] ifFalse:[
-            Autoload autoloadFailedSignal handle:[:ex |
-                'UserPreferences [warning]: autoload of ' , classNameToCheck , ' failed.' errorPrintCR.
-            ] do:[
-                classToCheck autoload.
-            ]
-        ]
+	classToCheck := Smalltalk at:classNameToCheck.
+	classToCheck isNil ifTrue:[
+	    ('UserPreferences [warning]: no class ' , classNameToCheck , ' class in system.') errorPrintCR.
+	] ifFalse:[
+	    Autoload autoloadFailedSignal handle:[:ex |
+		'UserPreferences [warning]: autoload of ' , classNameToCheck , ' failed.' errorPrintCR.
+	    ] do:[
+		classToCheck autoload.
+	    ]
+	]
     ].
 
     ^ super at:key asSymbol put:value
@@ -833,16 +833,16 @@
     "were to keep changes"
 
     ^self
-        at: #'changeFileName'
-        ifAbsent: nil
+	at: #'changeFileName'
+	ifAbsent: nil
 !
 
 changeFileName:aFilename
     "were to keep changes"
 
     self
-        at: #'changeFileName'
-        put: aFilename.
+	at: #'changeFileName'
+	put: aFilename.
 ! !
 
 !UserPreferences methodsFor:'accessing-locale'!
@@ -851,24 +851,24 @@
     "return a format used when tools read a date from the user"
 
     ^ self
-        at:#dateInputFormat
-        ifAbsentPut:[
-            (self language == #en and:[ self languageTerritory ~= #en])
-                ifTrue:[ '%m %d %y' ]
-                ifFalse:[ '%d %m %y' ]
-        ]
+	at:#dateInputFormat
+	ifAbsentPut:[
+	    (self language == #en and:[ self languageTerritory ~= #en])
+		ifTrue:[ '%m %d %y' ]
+		ifFalse:[ '%d %m %y' ]
+	]
 !
 
 dateInputFormat:aFormatString
     "return a format used when tools read a date from the user"
 
     ^ self
-        at:#dateInputFormat
-        ifAbsentPut:[
-            (self language == #en and:[ self languageTerritory ~= #en])
-                ifTrue:[ '%m %d %y' ]
-                ifFalse:[ '%d %m %y' ]
-        ]
+	at:#dateInputFormat
+	ifAbsentPut:[
+	    (self language == #en and:[ self languageTerritory ~= #en])
+		ifTrue:[ '%m %d %y' ]
+		ifFalse:[ '%d %m %y' ]
+	]
 
     "
      UserPreferences current dateInputFormat:'%d %m %y'  -- european
@@ -900,17 +900,17 @@
      This is rather user setting. To ask whether the selector namespaces
      support should be used, use:
 
-        UserPreferences current selectorNamespacesSupportedAndEnabled
+	UserPreferences current selectorNamespacesSupportedAndEnabled
     "
 
     ^self at:#selectorNamespacesEnabled ifAbsent:[false].
 
     "
-        UserPreferences current selectorNamespacesEnabled
-        UserPreferences current selectorNamespacesSupportedAndEnabled
-
-        UserPreferences current selectorNamespacesEnabled: true.
-        UserPreferences current selectorNamespacesEnabled: false.
+	UserPreferences current selectorNamespacesEnabled
+	UserPreferences current selectorNamespacesSupportedAndEnabled
+
+	UserPreferences current selectorNamespacesEnabled: true.
+	UserPreferences current selectorNamespacesEnabled: false.
     "
 
     "Created: / 19-07-2012 / 15:26:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -924,17 +924,17 @@
      This is rather user setting. To ask whether the selector namespaces
      are supported use
 
-        ConfigurableFeatures includesFeature:#SelectorNamespaces
+	ConfigurableFeatures includesFeature:#SelectorNamespaces
     "
 
     self at:#selectorNamespacesEnabled put: aBoolean
 
     "
-        UserPreferences current selectorNamespacesEnabled
-        UserPreferences current selectorNamespacesSupportedAndEnabled
-
-        UserPreferences current selectorNamespacesEnabled: true.
-        UserPreferences current selectorNamespacesEnabled: false.
+	UserPreferences current selectorNamespacesEnabled
+	UserPreferences current selectorNamespacesSupportedAndEnabled
+
+	UserPreferences current selectorNamespacesEnabled: true.
+	UserPreferences current selectorNamespacesEnabled: false.
     "
 
     "Created: / 19-07-2012 / 15:27:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -946,14 +946,14 @@
     "
 
     ^ (ConfigurableFeatures includesFeature:#SelectorNamespaces)
-        and:[self selectorNamespacesEnabled]
-
-    "
-        UserPreferences current selectorNamespacesEnabled
-        UserPreferences current selectorNamespacesSupportedAndEnabled
-
-        UserPreferences current selectorNamespacesEnabled: true.
-        UserPreferences current selectorNamespacesEnabled: false.
+	and:[self selectorNamespacesEnabled]
+
+    "
+	UserPreferences current selectorNamespacesEnabled
+	UserPreferences current selectorNamespacesSupportedAndEnabled
+
+	UserPreferences current selectorNamespacesEnabled: true.
+	UserPreferences current selectorNamespacesEnabled: false.
     "
 
     "Created: / 19-07-2012 / 15:32:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1101,8 +1101,8 @@
 
     className := self at: #changeSetBrowserClassName ifAbsent:[nil].
     className notNil ifTrue:[
-        class := Smalltalk at: className asSymbol.
-        class notNil ifTrue:[ ^ class ].
+	class := Smalltalk at: className asSymbol.
+	class notNil ifTrue:[ ^ class ].
     ].
 
     "Original code"
@@ -1110,7 +1110,7 @@
     "/^ Tools::ChangeSetBrowser2 ? ChangeSetBrowser
 
     self useNewChangeSetBrowser ifTrue:[
-        ^ Tools::ChangeSetBrowser2 ? ChangeSetBrowser
+	^ Tools::ChangeSetBrowser2 ? ChangeSetBrowser
     ].
     ^ ChangeSetBrowser ? Tools::ChangeSetBrowser2
 
@@ -1128,9 +1128,9 @@
     self at: #changeSetBrowserClassName put: aClass name.
 
     "
-        UserPreferences current changeSetBrowserClass
-        UserPreferences current changeSetBrowserClass: Tools::ChangeSetBrowser2.
-        UserPreferences current changeSetBrowserClass: ChangeSetBrowser.
+	UserPreferences current changeSetBrowserClass
+	UserPreferences current changeSetBrowserClass: Tools::ChangeSetBrowser2.
+	UserPreferences current changeSetBrowserClass: ChangeSetBrowser.
     "
 
     "Created: / 25-01-2012 / 17:08:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1143,13 +1143,13 @@
 
     className := self at: #changesBrowserClassName ifAbsent:[nil].
     className notNil ifTrue:[
-        class := Smalltalk at: className asSymbol.
-        class notNil ifTrue:[ ^ class ].
+	class := Smalltalk at: className asSymbol.
+	class notNil ifTrue:[ ^ class ].
     ].
 
     "/ Old code
     self useNewChangesBrowser ifTrue:[
-        ^ (NewChangesBrowser ? ChangesBrowser)
+	^ (NewChangesBrowser ? ChangesBrowser)
     ].
     ^ ChangesBrowser
 
@@ -1162,9 +1162,9 @@
     self at: #changesBrowserClassName put: aClass name.
 
     "
-        UserPreferences current changesBrowserClass
-        UserPreferences current changesBrowserClass: Tools::ChangeSetBrowser2.
-        UserPreferences current changesBrowserClass: ChangeSetBrowser.
+	UserPreferences current changesBrowserClass
+	UserPreferences current changesBrowserClass: Tools::ChangeSetBrowser2.
+	UserPreferences current changesBrowserClass: ChangeSetBrowser.
     "
 
     "Created: / 25-01-2012 / 17:12:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -1174,14 +1174,14 @@
     "the external command to use for diff"
 
     ^ self
-        at:#externalDiffCommandTemplate
-        ifAbsent:[
-            OperatingSystem isMSDOSlike ifTrue:[
-                'diff %1 %2'
-            ] ifFalse:[
-                'diff -b %1 %2'
-            ]
-        ]
+	at:#externalDiffCommandTemplate
+	ifAbsent:[
+	    OperatingSystem isMSDOSlike ifTrue:[
+		'diff %1 %2'
+	    ] ifFalse:[
+		'diff -b %1 %2'
+	    ]
+	]
 
     "
      UserPreferences current externalDiffCommandTemplate
@@ -1229,7 +1229,7 @@
 
 testRunnerClass
     self useTestRunner2 ifTrue:[
-        ^ Tools::TestRunner2 ? TestRunner
+	^ Tools::TestRunner2 ? TestRunner
     ].
     ^ TestRunner
 
@@ -1792,7 +1792,7 @@
 
     self at:#enableVMWareDrawingBugWorkaround put:aBoolean.
     Screen current platformName = 'X11' ifTrue:[
-        Screen current maxOperationsUntilFlush:(aBoolean ifTrue:[1] ifFalse:[nil])
+	Screen current maxOperationsUntilFlush:(aBoolean ifTrue:[1] ifFalse:[nil])
     ].
 
     "
@@ -1833,7 +1833,7 @@
 
 flyByHelpActive:aBoolean
     aBoolean ~~ self flyByHelpActive ifTrue:[
-        self at:#flyByHelpActive put:aBoolean.
+	self at:#flyByHelpActive put:aBoolean.
     ].
     self flyByHelpSettingChanged.
 !
@@ -1935,7 +1935,7 @@
 
 mouseWheelDirectionReversed
     "if set, mouse wheel motions are upside-down.
-     I got very confused with macOSX10.9, behavind different from 10.6, 
+     I got very confused with macOSX10.9, behavind different from 10.6,
      so I added this option"
 
     ^ self at:#mouseWheelDirectionReversed ifAbsent:[ false ]
@@ -1949,7 +1949,7 @@
 
 mouseWheelDirectionReversed:aBoolean
     "if set, mouse wheel motions are upside-down.
-     I got very confused with macOSX10.9, behavind different from 10.6, 
+     I got very confused with macOSX10.9, behavind different from 10.6,
      so I added this option"
 
     self at:#mouseWheelDirectionReversed put:aBoolean
@@ -2009,9 +2009,9 @@
     self at:#nativeDialogs put:aBoolean.
     currentScreen := Screen current.
     currentScreen notNil ifTrue:[
-        currentScreen supportsNativeDialogs ifTrue:[
-            currentScreen nativeDialogs:aBoolean
-        ].
+	currentScreen supportsNativeDialogs ifTrue:[
+	    currentScreen nativeDialogs:aBoolean
+	].
     ].
 
     "Modified: / 24-08-2010 / 18:06:43 / sr"
@@ -2029,9 +2029,9 @@
     self at:#nativeFileDialogs put:aBoolean.
     currentScreen := Screen current.
     currentScreen notNil ifTrue:[
-        currentScreen supportsNativeFileDialogs ifTrue:[
-            currentScreen nativeFileDialogs:aBoolean
-        ].
+	currentScreen supportsNativeFileDialogs ifTrue:[
+	    currentScreen nativeFileDialogs:aBoolean
+	].
     ].
 
     "Modified: / 24-08-2010 / 18:06:27 / sr"
@@ -2051,9 +2051,9 @@
     self at:#nativeWidgets put:aBoolean.
     currentScreen := Screen current.
     currentScreen notNil ifTrue:[
-        currentScreen supportsNativeWidgets ifTrue:[
-            currentScreen nativeWidgets:aBoolean
-        ].
+	currentScreen supportsNativeWidgets ifTrue:[
+	    currentScreen nativeWidgets:aBoolean
+	].
     ].
 
     "Created: / 24-08-2010 / 16:58:14 / sr"
@@ -2185,9 +2185,9 @@
 
 showDottedLinesInTree
     ^ self
-        at:#showDottedLinesInTree
-        ifAbsent:[ OperatingSystem isMSWINDOWSlike not
-                   or:[  OperatingSystem isVistaLike not ] ]
+	at:#showDottedLinesInTree
+	ifAbsent:[ OperatingSystem isMSWINDOWSlike not
+		   or:[  OperatingSystem isVistaLike not ] ]
 
     "Created: / 03-12-2010 / 11:31:46 / cg"
     "Modified: / 09-02-2011 / 23:27:03 / cg"
@@ -2260,8 +2260,8 @@
 
     self at:#toolTipAutoHideDelay put:aTimeDuration.
     FlyByHelp showTime: (aTimeDuration isInteger
-                            ifTrue:[aTimeDuration]
-                            ifFalse:[aTimeDuration asSeconds]).
+			    ifTrue:[aTimeDuration]
+			    ifFalse:[aTimeDuration asSeconds]).
 
     "
      UserPreferences current toolTipAutoHideDelay:10 seconds
@@ -2605,15 +2605,15 @@
 
     clr := self at:#colorForInstrumentedFullyCoveredCode ifAbsent:nil.
     clr isNil ifTrue:[
-        clr := Color green slightlyDarkened "darkened".
-        "/ self at:#colorForInstrumentedFullyCoveredCode put:clr.
+	clr := Color green slightlyDarkened "darkened".
+	"/ self at:#colorForInstrumentedFullyCoveredCode put:clr.
     ].
     ^ clr
 
     "
      UserPreferences current
-        at:#emphasisForInstrumentedFullyCoveredCode
-        put:(Color green slightlyDarkened).
+	at:#emphasisForInstrumentedFullyCoveredCode
+	put:(Color green slightlyDarkened).
     "
 
     "Created: / 28-04-2010 / 13:58:52 / cg"
@@ -2640,15 +2640,15 @@
 
     clr := self at:#colorForInstrumentedNeverCalledCode ifAbsent:nil.
     clr isNil ifTrue:[
-        clr := Color red "slightlyDarkened" "darkened".
-        "/ self at:#colorForInstrumentedNeverCalledCode put:clr.
+	clr := Color red "slightlyDarkened" "darkened".
+	"/ self at:#colorForInstrumentedNeverCalledCode put:clr.
     ].
     ^ clr
 
     "
      UserPreferences current
-        at:#colorForInstrumentedNeverCalledCode
-        put:(Color red slightlyDarkened).
+	at:#colorForInstrumentedNeverCalledCode
+	put:(Color red slightlyDarkened).
     "
 
     "Created: / 28-04-2010 / 13:59:43 / cg"
@@ -2675,15 +2675,15 @@
 
     clr := self at:#colorForInstrumentedPartiallyCoveredCode ifAbsent:nil.
     clr isNil ifTrue:[
-        clr := Color orange "slightlyDarkened".
-        "/ self at:#colorForInstrumentedPartiallyCoveredCode put:clr.
+	clr := Color orange "slightlyDarkened".
+	"/ self at:#colorForInstrumentedPartiallyCoveredCode put:clr.
     ].
     ^ clr
 
     "
      UserPreferences current
-        at:#colorForInstrumentedPartiallyCoveredCode
-        put:(Color orange slightlyLightened).
+	at:#colorForInstrumentedPartiallyCoveredCode
+	put:(Color orange slightlyLightened).
     "
 
     "Created: / 28-04-2010 / 14:00:56 / cg"
@@ -2709,22 +2709,22 @@
     |bg|
 
     SelectionInListView notNil ifTrue:[
-        bg := SelectionInListView defaultBackgroundColor.
+	bg := SelectionInListView defaultBackgroundColor.
     ].
     bg isNil ifTrue:[
-        View notNil ifTrue:[
-            bg := View defaultBackgroundColor.
-        ].
-        bg isNil ifTrue:[
-            ^ Color gray
-        ].
+	View notNil ifTrue:[
+	    bg := View defaultBackgroundColor.
+	].
+	bg isNil ifTrue:[
+	    ^ Color gray
+	].
     ].
 
     (Color gray brightness - (bg brightness)) abs < 0.3 ifTrue:[
-        (bg brightness) > 0.7 ifTrue:[
-            ^ Color gray:20.
-        ].
-        ^ Color gray:80.
+	(bg brightness) > 0.7 ifTrue:[
+	    ^ Color gray:20.
+	].
+	^ Color gray:80.
     ].
     ^ Color gray
 
@@ -2801,17 +2801,17 @@
 
     emp := self at:#emphasisForInstrumentedFullyCoveredCode ifAbsent:nil.
     emp isNil ifTrue:[
-        emp := #color->Color green slightlyDarkened.
-        emp := Array with:#bold with:emp.
-        "/ emp := #color->Color blue darkened.
-        self at:#emphasisForInstrumentedFullyCoveredCode put:emp.
+	emp := #color->Color green slightlyDarkened.
+	emp := Array with:#bold with:emp.
+	"/ emp := #color->Color blue darkened.
+	self at:#emphasisForInstrumentedFullyCoveredCode put:emp.
     ].
     ^ emp
 
     "
      UserPreferences current
-        at:#emphasisForInstrumentedFullyCoveredCode
-        put:(Array with:#bold with:(#color->Color green slightlyDarkened)).
+	at:#emphasisForInstrumentedFullyCoveredCode
+	put:(Array with:#bold with:(#color->Color green slightlyDarkened)).
     "
 
     "Created: / 27-04-2010 / 13:01:01 / cg"
@@ -2825,17 +2825,17 @@
 
     emp := self at:#emphasisForInstrumentedNeverCalledCode ifAbsent:nil.
     emp isNil ifTrue:[
-        emp := #color->Color red slightlyDarkened.
-        emp := Array with:#bold with:emp.
-        "/ emp := #color->Color blue darkened.
-        self at:#emphasisForInstrumentedNeverCalledCode put:emp.
+	emp := #color->Color red slightlyDarkened.
+	emp := Array with:#bold with:emp.
+	"/ emp := #color->Color blue darkened.
+	self at:#emphasisForInstrumentedNeverCalledCode put:emp.
     ].
     ^ emp
 
     "
      UserPreferences current
-        at:#emphasisForInstrumentedNeverCalledCode
-        put:(Array with:#bold with:(#color->Color red slightlyDarkened)).
+	at:#emphasisForInstrumentedNeverCalledCode
+	put:(Array with:#bold with:(#color->Color red slightlyDarkened)).
     "
 
     "Created: / 27-04-2010 / 12:59:47 / cg"
@@ -2850,17 +2850,17 @@
 
     emp := self at:#emphasisForInstrumentedPartiallyCoveredCode ifAbsent:nil.
     emp isNil ifTrue:[
-        emp := #color->Color orange.
-        emp := Array with:#bold with:emp.
-        "/ emp := #color->Color blue darkened.
-        self at:#emphasisForInstrumentedPartiallyCoveredCode put:emp.
+	emp := #color->Color orange.
+	emp := Array with:#bold with:emp.
+	"/ emp := #color->Color blue darkened.
+	self at:#emphasisForInstrumentedPartiallyCoveredCode put:emp.
     ].
     ^ emp
 
     "
      UserPreferences current
-        at:#emphasisForInstrumentedPartiallyCoveredCode
-        put:(Array with:#bold with:(#color->Color orange slightlyLightened)).
+	at:#emphasisForInstrumentedPartiallyCoveredCode
+	put:(Array with:#bold with:(#color->Color orange slightlyLightened)).
     "
 
     "Created: / 27-04-2010 / 13:01:20 / cg"
@@ -2890,10 +2890,10 @@
 
     emp := self at:#emphasisForNamespacedCode ifAbsent:nil.
     emp isNil ifTrue:[
-        emp := #color->Color green darkened.
-        "/ emp := Array with:#bold with:emp.
-        "/ emp := #color->Color blue darkened.
-        self at:#emphasisForNamespacedCode put:emp.
+	emp := #color->Color green darkened.
+	"/ emp := Array with:#bold with:emp.
+	"/ emp := #color->Color blue darkened.
+	self at:#emphasisForNamespacedCode put:emp.
     ].
     ^ emp
 
@@ -3193,24 +3193,24 @@
      If syntaxColoring is turned on."
 
     ^ self
-        at:#defaultSyntaxEmphasis
-        ifAbsentPut:[UserPreferences default at:#defaultSyntaxEmphasis ifAbsent:#normal]
+	at:#defaultSyntaxEmphasis
+	ifAbsentPut:[UserPreferences default at:#defaultSyntaxEmphasis ifAbsent:#normal]
 
     "Modified: / 21-04-2011 / 12:34:46 / cg"
 !
 
 doesNotUnderstand:aMessage
-    |k def|
+    |k def numArgs|
 
     k := aMessage selector.
-    aMessage numArgs == 0 ifTrue:[
-        (self includesKey:k) ifTrue:[
-            ^ self at:k
-        ].
-        ((def := self class default) includesKey:k) ifTrue:[
-            ^ def at:k
-        ].
-        ^ self defaultValue
+    (numArgs := aMessage numArgs) == 0 ifTrue:[
+	(self includesKey:k) ifTrue:[
+	    ^ self at:k
+	].
+	((def := self class default) includesKey:k) ifTrue:[
+	    ^ def at:k
+	].
+	^ self defaultValue
     ].
 
     "/ this is needed, if a setting is loaded (via the settings.stx) at a time
@@ -3219,16 +3219,15 @@
     "/ if obsolete keys accumulate over time, we might need a settings cleanup GUI to
     "/ care for that.
 
-    ((aMessage numArgs == 1)
-    and:[ (k endsWith:$:)])
+    ((numArgs == 1) and:[ (k endsWith:$:)])
     ifTrue:[
-        k := (k copyButLast) asSymbol.
-        ^ self at:k put:(aMessage arg1)
+	k := (k copyButLast) asSymbol.
+	^ self at:k put:(aMessage arg1)
     ].
 
-    aMessage numArgs == 1 ifTrue:[
-        ('UserPreferences [info]: obsolete settings key: ' , aMessage selector , ' - ignored.') infoPrintCR.
-        ^ nil
+    numArgs == 1 ifTrue:[
+	('UserPreferences [info]: obsolete settings key: ' , aMessage selector , ' - ignored.') infoPrintCR.
+	^ nil
     ].
 
     ^ super doesNotUnderstand:aMessage
@@ -4021,11 +4020,11 @@
 
 variableBackgroundColorForNavigationService
     ^ self
-        at: #variableBackgroundColorForNavigationService
-        ifAbsent: [
-            (Color rgbValue:16rFFFFA7)
-            "/ (Color rgbValue:16rEFD7A7)
-        ]
+	at: #variableBackgroundColorForNavigationService
+	ifAbsent: [
+	    (Color rgbValue:16rFFFFA7)
+	    "/ (Color rgbValue:16rEFD7A7)
+	]
 
     "Modified: / 01-10-2013 / 11:35:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
@@ -4040,8 +4039,8 @@
     Smalltalk loadPackage:packageName.
 
     "
-     UserPreferences current addPreloadedPackage:'stx:goodies/smallsense' 
-     UserPreferences current removePreloadedPackage:'stx:goodies/smallsense' 
+     UserPreferences current addPreloadedPackage:'stx:goodies/smallsense'
+     UserPreferences current removePreloadedPackage:'stx:goodies/smallsense'
     "
 !
 
@@ -4052,9 +4051,9 @@
     ^ self at:#preloadedPackages ifAbsent:[ #() ].
 
     "
-     UserPreferences current addPreloadedPackage:'stx:goodies/smallsense' 
-     UserPreferences current removePreloadedPackage:'stx:goodies/smallsense' 
-     UserPreferences current preloadedPackages 
+     UserPreferences current addPreloadedPackage:'stx:goodies/smallsense'
+     UserPreferences current removePreloadedPackage:'stx:goodies/smallsense'
+     UserPreferences current preloadedPackages
     "
 !
 
@@ -4067,13 +4066,13 @@
     set := setOfPreloadedPackages asSet.
     self at:#preloadedPackages put:set.
     set do:[:each |
-        Smalltalk loadPackage:each
+	Smalltalk loadPackage:each
     ].
 
     "
-     UserPreferences current addPreloadedPackage:'stx:goodies/smallsense' 
-     UserPreferences current removePreloadedPackage:'stx:goodies/smallsense' 
-     UserPreferences current preloadedPackages 
+     UserPreferences current addPreloadedPackage:'stx:goodies/smallsense'
+     UserPreferences current removePreloadedPackage:'stx:goodies/smallsense'
+     UserPreferences current preloadedPackages
     "
 !
 
@@ -4084,8 +4083,8 @@
     (self at:#preloadedPackages ifAbsentPut:[Set new]) remove:packageName ifAbsent:[]
 
     "
-     UserPreferences current addPreloadedPackage:'stx:goodies/smallsense' 
-     UserPreferences current removePreloadedPackage:'stx:goodies/smallsense' 
+     UserPreferences current addPreloadedPackage:'stx:goodies/smallsense'
+     UserPreferences current removePreloadedPackage:'stx:goodies/smallsense'
     "
 ! !
 
@@ -4348,11 +4347,11 @@
     "Returns selection extension mode. Mode is either
 
     #traditional ... Shift-End always moves end of selection (iff it is on the same line)
-                     Shift->Home always moves beggining of selection (iff it is on the same line)
-                     That's how CG likes it.
+		     Shift->Home always moves beggining of selection (iff it is on the same line)
+		     That's how CG likes it.
 
     #standard ...    That's how vast majority text editors and text widgets behaves, therefore
-                     this is how most users expects it to behave.
+		     this is how most users expects it to behave.
 
 
     For historical reasons, #traditional is the default..."
@@ -4379,22 +4378,22 @@
     "Sets selection extension mode. Must be either:
 
     #traditional ... Shift-End always moves end of selection (iff it is on the same line)
-                     Shift->Home always moves beggining of selection (iff it is on the same line)
-                     That's how CG likes it.
+		     Shift->Home always moves beggining of selection (iff it is on the same line)
+		     That's how CG likes it.
 
     #standard ...    That's how vast majority text editors and text widgets behaves, therefore
-                     this is how most users expects it to behave.
+		     this is how most users expects it to behave.
 
 
     For historical reasons, #traditional is the default..."
 
     aSymbol isNil ifTrue:[
-        self removeKey:#selectionExtensionMode.
-        ^ self.
+	self removeKey:#selectionExtensionMode.
+	^ self.
     ].
 
     (#(traditional standard) includes: aSymbol) ifFalse:[
-        self error:'Invalid value. Possible values are #traditional and #standard'.
+	self error:'Invalid value. Possible values are #traditional and #standard'.
     ].
     self at: #selectionExtensionMode put: aSymbol
 
@@ -4706,10 +4705,10 @@
 
     self at:#autoRaiseTranscript put:aBoolean.
     (self == UserPreferences current) ifTrue:[
-        transcript := Transcript current.
-        (transcript notNil and:[transcript isExternalStream not]) ifTrue:[
-            transcript autoRaise:aBoolean.
-        ].
+	transcript := Transcript current.
+	(transcript notNil and:[transcript isExternalStream not]) ifTrue:[
+	    transcript autoRaise:aBoolean.
+	].
     ].
 
     "
@@ -4859,10 +4858,10 @@
      the terminal emulator."
 
     ^ self
-        at:#terminalOutputIsUTF8
-        ifAbsent:[ OperatingSystem isOSXlike
-                   "/ or ???
-                 ]
+	at:#terminalOutputIsUTF8
+	ifAbsent:[ OperatingSystem isOSXlike
+		   "/ or ???
+		 ]
 
     "
      UserPreferences current terminalOutputIsUTF8
@@ -4874,8 +4873,8 @@
      the terminal emulator."
 
     ^ self
-        at:#terminalOutputIsUTF8
-        put:aBoolean
+	at:#terminalOutputIsUTF8
+	put:aBoolean
 
     "
      UserPreferences current terminalOutputIsUTF8
@@ -5070,19 +5069,19 @@
      (as shown in the Launchers 'source and debugger settings' dialog."
 
     ^ #(
-            (#resetSyntaxColors                                         'default [ST/X style]')
-            (#resetSyntaxColorsWithSideEffectHighlighting               'default with side effect highlighting [new ST/X style]')
-            (#resetSyntaxColorsToVCStyle                                'green comments; blue controlFlow, red constants [VISUAL-C style]')
-            (#resetSyntaxColorsBlueControlFlowSelectors                 'blue controlFlow')
-            (#resetSyntaxColorsGreenComments                            'green comments')
-            (#resetSyntaxColorsGreenCommentsBlueControlFlowSelectors    'green comments; blue controlFlow')
-            (#resetSyntaxColorsBlueSelectorsGreenComments               'blue selectors; green comments [DOLPHIN style]')
-            (#resetSyntaxColorsBlueSelectorsGreyComments                'blue selectors; grey comments')
-            (#resetSyntaxColorsToSqueakStyle1                           'blue selectors; green comments [SQUEAK style]')
-            (#resetSyntaxColorsToSqueakStyle2                           'blue selectors; green comments; brown self [new SQUEAK style]')
-            (#resetSyntaxColorsAllBlackExceptBadIDs                     'no colors, but highlight errors')
-            (#resetSyntaxColorsToVAgeStyle                              'blue globals; green comments [V''Age style]')
-            (#resetSyntaxColorsToVW7Style                               'light blue comments [VW7 style]')
+	    (#resetSyntaxColors                                         'default [ST/X style]')
+	    (#resetSyntaxColorsWithSideEffectHighlighting               'default with side effect highlighting [new ST/X style]')
+	    (#resetSyntaxColorsToVCStyle                                'green comments; blue controlFlow, red constants [VISUAL-C style]')
+	    (#resetSyntaxColorsBlueControlFlowSelectors                 'blue controlFlow')
+	    (#resetSyntaxColorsGreenComments                            'green comments')
+	    (#resetSyntaxColorsGreenCommentsBlueControlFlowSelectors    'green comments; blue controlFlow')
+	    (#resetSyntaxColorsBlueSelectorsGreenComments               'blue selectors; green comments [DOLPHIN style]')
+	    (#resetSyntaxColorsBlueSelectorsGreyComments                'blue selectors; grey comments')
+	    (#resetSyntaxColorsToSqueakStyle1                           'blue selectors; green comments [SQUEAK style]')
+	    (#resetSyntaxColorsToSqueakStyle2                           'blue selectors; green comments; brown self [new SQUEAK style]')
+	    (#resetSyntaxColorsAllBlackExceptBadIDs                     'no colors, but highlight errors')
+	    (#resetSyntaxColorsToVAgeStyle                              'blue globals; green comments [V''Age style]')
+	    (#resetSyntaxColorsToVW7Style                               'light blue comments [VW7 style]')
       )
 
     "Modified: / 17-03-2012 / 10:40:18 / cg"
@@ -5296,11 +5295,11 @@
 
 flyByHelpSettingChanged
     FlyByHelp notNil ifTrue:[
-        (self at:#flyByHelpActive ifAbsent:true) ifTrue:[
-            FlyByHelp start.
-        ] ifFalse:[
-            FlyByHelp stop.
-        ].
+	(self at:#flyByHelpActive ifAbsent:true) ifTrue:[
+	    FlyByHelp start.
+	] ifFalse:[
+	    FlyByHelp stop.
+	].
     ].
 ! !
 
@@ -5337,14 +5336,13 @@
 !UserPreferences class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.403 2015-03-09 11:00:27 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.404 2015-04-22 12:24:40 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.403 2015-03-09 11:00:27 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.404 2015-04-22 12:24:40 cg Exp $'
 !
 
 version_SVN
     ^ '$ Id: UserPreferences.st 10648 2011-06-23 15:55:10Z vranyj1  $'
 ! !
-