Merged with /trunk jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Tue, 05 Jun 2012 14:35:12 +0100
branchjv
changeset 17944 084a2c804b87
parent 17943 1d2620126660
child 17945 3b36feb6e349
Merged with /trunk
Behavior.st
Block.st
CharacterArray.st
Class.st
CompiledCode.st
Context.st
Method.st
ProgrammingLanguage.st
SequenceableCollection.st
String.st
UninterpretedBytes.st
UserPreferences.st
--- a/Behavior.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/Behavior.st	Tue Jun 05 14:35:12 2012 +0100
@@ -1024,6 +1024,16 @@
     ^ (self == Behavior class) or:[self == Behavior]
 
     "Modified: 23.4.1996 / 15:55:52 / cg"
+!
+
+supportsMethodCategories
+    "return true, if my methods are categorized.
+     This is a hook for the browser to allow alien classes
+     to be handled (actually, this is not yet used)."
+
+    ^ true
+
+    "Created: / 01-06-2012 / 20:37:46 / cg"
 ! !
 
 !Behavior methodsFor:'Compatibility-Dolphin'!
@@ -3283,12 +3293,12 @@
 supportsMethodCategories
     "return true, if my methods are categorized.
      This is a hook for the browser to allow alien classes
-     to be handled (aktually, this is not yet used)."
-
-    ^ true
-
-    "Created: 30.7.1997 / 14:59:08 / cg"
-    "Modified: 30.7.1997 / 15:02:03 / cg"
+     to be handled (actually, this is not yet used)."
+
+    ^ self class supportsMethodCategories
+
+    "Created: / 30-07-1997 / 14:59:08 / cg"
+    "Modified: / 01-06-2012 / 20:38:03 / cg"
 !
 
 theMetaclass
@@ -4767,13 +4777,13 @@
 !Behavior class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.319 2012/03/17 18:57:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.320 2012/06/01 21:37:36 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.319 2012/03/17 18:57:17 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.320 2012/06/01 21:37:36 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Behavior.st 10801 2012-04-06 12:43:09Z kursjan $'
+    ^ '$Id: Behavior.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
--- a/Block.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/Block.st	Tue Jun 05 14:35:12 2012 +0100
@@ -11,7 +11,7 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-CompiledCode variableSubclass:#Block
+CompiledCode subclass:#Block
 	instanceVariableNames:'home nargs sourcePos initialPC'
 	classVariableNames:'InvalidNewSignal'
 	poolDictionaries:''
@@ -101,71 +101,71 @@
 examples
 "
     define a block and evaluate it:
-									[exBegin]
-	|b|
-
-	b := [ Transcript showCR:'hello' ].
-
-	Transcript showCR:'now evaluating the block ...'.
-	b value.
-									[exEnd]
+                                                                        [exBegin]
+        |b|
+
+        b := [ Transcript showCR:'hello' ].
+
+        Transcript showCR:'now evaluating the block ...'.
+        b value.
+                                                                        [exEnd]
 
 
 
     even here, blocks are involved: 
     (although, the compiler optimizes things if possible)
-									[exBegin]
-	Transcript showCR:'now evaluating one of two blocks ...'.
-	1 > 4 ifTrue:[
-	    Transcript showCR:'foo'
-	] ifFalse:[
-	    Transcript showCR:'bar'
-	]
-									[exEnd]
+                                                                        [exBegin]
+        Transcript showCR:'now evaluating one of two blocks ...'.
+        1 > 4 ifTrue:[
+            Transcript showCR:'foo'
+        ] ifFalse:[
+            Transcript showCR:'bar'
+        ]
+                                                                        [exEnd]
 
 
 
     here things become obvious:
-									[exBegin]
-	|yesBlock noBlock|
-
-	yesBlock := [ Transcript showCR:'foo' ].
-	noBlock := [ Transcript showCR:'bar' ].
-
-	Transcript showCR:'now evaluating one of two blocks ...'.
-	1 > 4 ifTrue:yesBlock
-	      ifFalse:noBlock
-									[exEnd]
+                                                                        [exBegin]
+        |yesBlock noBlock|
+
+        yesBlock := [ Transcript showCR:'foo' ].
+        noBlock := [ Transcript showCR:'bar' ].
+
+        Transcript showCR:'now evaluating one of two blocks ...'.
+        1 > 4 ifTrue:yesBlock
+              ifFalse:noBlock
+                                                                        [exEnd]
 
 
 
     simple loops:
       not very objectOriented:
-									[exBegin]
-	|i|
-
-	i := 1.
-	[i < 10] whileTrue:[
-	    Transcript showCR:i.
-	    i := i + 1
-	]
-									[exEnd]
+                                                                        [exBegin]
+        |i|
+
+        i := 1.
+        [i < 10] whileTrue:[
+            Transcript showCR:i.
+            i := i + 1
+        ]
+                                                                        [exEnd]
 
 
       using integer protocol:
-									[exBegin]
-	1 to:10 do:[:i |
-	    Transcript showCR:i.
-	]
-									[exEnd]
+                                                                        [exBegin]
+        1 to:10 do:[:i |
+            Transcript showCR:i.
+        ]
+                                                                        [exEnd]
 
 
       interval protocol:
-									[exBegin]
-	(1 to:10) do:[:i |
-	    Transcript showCR:i.
-	]
-									[exEnd]
+                                                                        [exBegin]
+        (1 to:10) do:[:i |
+            Transcript showCR:i.
+        ]
+                                                                        [exEnd]
 
 
 
@@ -173,131 +173,131 @@
 
       bad code:
       (only works with numeric-indexable collections)
-									[exBegin]
-	|i coll|
-
-	coll := #(9 8 7 6 5).
-	i := 1.
-	[i <= coll size] whileTrue:[
-	    Transcript showCR:(coll at:i).
-	    i := i + 1.
-	]
-									[exEnd]
+                                                                        [exBegin]
+        |i coll|
+
+        coll := #(9 8 7 6 5).
+        i := 1.
+        [i <= coll size] whileTrue:[
+            Transcript showCR:(coll at:i).
+            i := i + 1.
+        ]
+                                                                        [exEnd]
 
 
 
       just as bad (well, marginally better ;-):
       (only works with numeric-indexable collections)
-									[exBegin]
-	|coll|   
-
-	coll := #(9 8 7 6 5).
-	1 to:coll size do:[:i |
-	    Transcript showCR:(coll at:i).
-	]
-									[exEnd]
+                                                                        [exBegin]
+        |coll|   
+
+        coll := #(9 8 7 6 5).
+        1 to:coll size do:[:i |
+            Transcript showCR:(coll at:i).
+        ]
+                                                                        [exEnd]
 
 
 
       the smalltalk way:
       (works with any collection)
-									[exBegin]
-	|coll|   
-
-	coll := #(9 8 7 6 5).
-	coll do:[:element |
-	    Transcript showCR:element.
-	]
-									[exEnd]
+                                                                        [exBegin]
+        |coll|   
+
+        coll := #(9 8 7 6 5).
+        coll do:[:element |
+            Transcript showCR:element.
+        ]
+                                                                        [exEnd]
         
     Rule: use enumeration protocol of the collection instead of
-	  manually indexing it. [with few exceptions]
+          manually indexing it. [with few exceptions]
 
 
 
     processes:
 
       forking a lightweight process (thread):
-									[exBegin]
-	[
-	    Transcript showCR:'waiting ...'.
-	    Delay waitForSeconds:2.
-	    Transcript showCR:'here I am'.
-	] fork
-									[exEnd]
+                                                                        [exBegin]
+        [
+            Transcript showCR:'waiting ...'.
+            Delay waitForSeconds:2.
+            Transcript showCR:'here I am'.
+        ] fork
+                                                                        [exEnd]
 
 
         
       some with low prio:
-									[exBegin]
-	[
-	    Transcript showCR:'computing ...'.
-	    10000 factorial.
-	    Transcript showCR:'here I am'.
-	] forkAt:(Processor userBackgroundPriority)
-									[exEnd]
+                                                                        [exBegin]
+        [
+            Transcript showCR:'computing ...'.
+            10000 factorial.
+            Transcript showCR:'here I am'.
+        ] forkAt:(Processor userBackgroundPriority)
+                                                                        [exEnd]
 
 
 
     handling exceptions:
-									[exBegin]
-	Object errorSignal handle:[:ex |
-	    Transcript showCR:'exception handler forces return'.
-	    ex return
-	] do:[
-	    Transcript showCR:'now, doing something bad ...'.
-	    1 / 0.
-	    Transcript showCR:'not reached'
-	]
-									[exEnd]
+                                                                        [exBegin]
+        Error handle:[:ex |
+            Transcript showCR:'exception handler forces return'.
+            ex return
+        ] do:[
+            Transcript showCR:'now, doing something bad ...'.
+            1 / 0.
+            Transcript showCR:'not reached'
+        ]
+                                                                        [exEnd]
 
 
 
     performing cleanup actions:
-									[exBegin]
-	Object errorSignal handle:[:ex |
-	    Transcript showCR:'exception handler forces return'.
-	    ex return
-	] do:[
-	    [
-		Transcript showCR:'doing something bad ...'.
-		1 / 0.
-		Transcript showCR:'not reached'
-	    ] valueOnUnwindDo:[
-		Transcript showCR:'cleanup'
-	    ]
-	]
-									[exEnd]
+                                                                        [exBegin]
+        Error handle:[:ex |
+            Transcript showCR:'exception handler forces return'.
+            ex return
+        ] do:[
+            [
+                Transcript showCR:'doing something bad ...'.
+                1 / 0.
+                Transcript showCR:'not reached'
+            ] ifCurtailed:[
+                Transcript showCR:'cleanup'
+            ]
+        ]
+                                                                        [exEnd]
 
 
     delayed execution (visitor pattern):
     (looking carefully into the example, 
      C/C++ programmers may raise their eyes ;-)
-									[exBegin]
-	|showBlock countBlock 
-	 howMany 
-	 top panel b1 b2|
-
-	howMany := 0.
-
-	showBlock := [ Transcript showCR:howMany ].
-	countBlock := [ howMany := howMany + 1 ].
-
-	top := StandardSystemView extent:200@200.
-	panel := HorizontalPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
-
-	b1 := Button label:'count up' in:panel.
-	b1 action:countBlock.
-
-	b2 := Button label:'show value' in:panel.
-	b2 action:showBlock.
-
-	top open.
-
-	Transcript showCR:'new process started;'.
-	Transcript showCR:'notice: the blocks can still access the'.
-	Transcript showCR:'        howMany local variable.'.
-									[exEnd]
+                                                                        [exBegin]
+        |showBlock countBlock 
+         howMany 
+         top panel b1 b2|
+
+        howMany := 0.
+
+        showBlock := [ Transcript showCR:howMany ].
+        countBlock := [ howMany := howMany + 1 ].
+
+        top := StandardSystemView extent:200@200.
+        panel := HorizontalPanelView origin:0.0@0.0 corner:1.0@1.0 in:top.
+
+        b1 := Button label:'count up' in:panel.
+        b1 action:countBlock.
+
+        b2 := Button label:'show value' in:panel.
+        b2 action:showBlock.
+
+        top open.
+
+        Transcript showCR:'new process started;'.
+        Transcript showCR:'notice: the blocks can still access the'.
+        Transcript showCR:'        howMany local variable.'.
+                                                                        [exEnd]
 "
 ! !
 
@@ -370,8 +370,6 @@
     "Modified: 23.4.1996 / 15:55:58 / cg"
 ! !
 
-
-
 !Block methodsFor:'Compatibility-ANSI'!
 
 argumentCount
@@ -546,19 +544,82 @@
 
 !Block methodsFor:'Compatibility-V''Age'!
 
-valueOnReturnDo:aBlock
-    "VisualAge compatibility: alias for #ifCurtailed:
-     evaluate the receiver - when some method sent within unwinds 
-     (i.e. does a long return), evaluate the argument, aBlock.
+apply:aCollection from:start to:end
+    "Evaluate the receiver for each variable slot of aCollection from start to end. 
+     Answer aCollection."
+
+    aCollection from:start to:end do:self.
+    ^ aCollection
+
+    "
+     [:i | Transcript showCR:i ]
+        apply:#(10 20 30 40 50 60) from:2 to:4
+    "
+
+    "Created: / 16-05-2012 / 11:20:55 / cg"
+!
+
+applyWithIndex:aCollection from:start to:end
+    "Evaluate the receiver for each variable slot and index of aCollection from start to end. 
+     Answer aCollection."
+
+    aCollection from:start to:end doWithIndex:self.
+    ^ aCollection
+
+    "
+     [:el :i | Transcript showCR:(i -> el) ]
+        applyWithIndex:#(10 20 30 40 50 60) from:2 to:4
+    "
+
+    "Created: / 16-05-2012 / 11:22:01 / cg"
+!
+
+value:arg1 onReturnDo:aBlock
+    "VisualAge compatibility: alias for #ensure:
+     evaluate the receiver - when the block returns either a local return
+     or an unwind (i.e. does a long return), evaluate the argument, aBlock.
      This is used to make certain that cleanup actions 
-     (for example closing files etc.) are executed regardless of error actions.
-
-     Q: is this the exact semantics of V'Ages method ?
-	the documentation is unclean; it could be a valueNowOrOnUnwindDo: ..."
-
-    ^ self ifCurtailed:aBlock
-
-    "Created: 15.11.1996 / 11:38:37 / cg"
+     (for example closing files etc.) are executed regardless of error actions."
+
+    ^ [self value:arg1] ensure:aBlock
+
+    "Created: / 16-05-2012 / 11:29:30 / cg"
+!
+
+value:arg1 value:arg2 onReturnDo:aBlock
+    "VisualAge compatibility: alias for #ensure:
+     evaluate the receiver - when the block returns either a local return
+     or an unwind (i.e. does a long return), evaluate the argument, aBlock.
+     This is used to make certain that cleanup actions 
+     (for example closing files etc.) are executed regardless of error actions."
+
+    ^ [self value:arg1 value:arg2] ensure:aBlock
+
+    "Created: / 16-05-2012 / 11:29:46 / cg"
+!
+
+value:arg1 value:arg2 value:arg3 onReturnDo:aBlock
+    "VisualAge compatibility: alias for #ensure:
+     evaluate the receiver - when the block returns either a local return
+     or an unwind (i.e. does a long return), evaluate the argument, aBlock.
+     This is used to make certain that cleanup actions 
+     (for example closing files etc.) are executed regardless of error actions."
+
+    ^ [self value:arg1 value:arg2 value:arg3] ensure:aBlock
+
+    "Created: / 16-05-2012 / 11:29:59 / cg"
+!
+
+valueOnReturnDo:aBlock
+    "VisualAge compatibility: alias for #ensure:
+     evaluate the receiver - when the block returns either a local return
+     or an unwind (i.e. does a long return), evaluate the argument, aBlock.
+     This is used to make certain that cleanup actions 
+     (for example closing files etc.) are executed regardless of error actions."
+
+    ^ self ensure:aBlock
+
+    "Created: / 15-11-1996 / 11:38:37 / cg"
 !
 
 when:exceptionClassOrSignal do:handler
@@ -567,7 +628,6 @@
     "Created: / 28-08-2010 / 14:41:15 / cg"
 ! !
 
-
 !Block methodsFor:'accessing'!
 
 home
@@ -625,7 +685,6 @@
     ^ nargs
 ! !
 
-
 !Block methodsFor:'compatibility-Cola & Pepsi'!
 
 arity
@@ -2968,18 +3027,15 @@
 !Block class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Block.st,v 1.186 2011/10/04 12:56:53 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Block.st,v 1.188 2012/05/22 09:58:15 stefan Exp $'
 !
 
 version_CVS
-    ^ 'Header: /cvs/stx/stx/libbasic/Block.st,v 1.186 2011/10/04 12:56:53 cg Exp '
+    ^ '§Header: /cvs/stx/stx/libbasic/Block.st,v 1.188 2012/05/22 09:58:15 stefan Exp §'
 !
 
 version_SVN
-    ^ '$Id: Block.st 10761 2012-01-19 11:46:00Z vranyj1 $'
+    ^ '$Id: Block.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
 
 Block initialize!
-
-
-
--- a/CharacterArray.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/CharacterArray.st	Tue Jun 05 14:35:12 2012 +0100
@@ -1740,7 +1740,7 @@
 !
 
 lastIndexOfSeparator
-    "return the last index of the whitespace character.
+    "return the last index of a whitespace character (space or tab).
      (i.e. start the search at the end and search backwards);
      Returns 0 if no separator is found."
 
@@ -1752,6 +1752,8 @@
      'hel lo wor ld' lastIndexOfSeparator
      'hel   ' lastIndexOfSeparator 6
     "
+
+    "Modified (comment): / 01-06-2012 / 13:10:30 / cg"
 !
 
 lastIndexOfSeparatorStartingAt:startIndex
@@ -3054,6 +3056,10 @@
     "thats not really true - characters above ascii 16r7F may need special treatment"
 
     ^ ((UnicodeString new:self size) replaceFrom:1 to:self size with:self startingAt:1)
+
+    "
+        'Hello World' asUnicodeString
+    "
 !
 
 asUnixFilename
@@ -4270,7 +4276,6 @@
     "Created: / 08-03-2012 / 03:11:11 / cg"
 ! !
 
-
 !CharacterArray methodsFor:'padded copying'!
 
 centerPaddedTo:newSize
@@ -4791,7 +4796,6 @@
     "Modified: 17.4.1997 / 12:50:23 / cg"
 ! !
 
-
 !CharacterArray methodsFor:'special string converting'!
 
 expandPlaceholdersWith:argArrayOrDictionary
@@ -6075,15 +6079,15 @@
 !CharacterArray class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.471 2012/04/24 14:56:08 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.474 2012/06/01 11:11:52 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.471 2012/04/24 14:56:08 stefan Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/CharacterArray.st,v 1.474 2012/06/01 11:11:52 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: CharacterArray.st 10807 2012-05-05 21:58:24Z vranyj1 $'
+    ^ '$Id: CharacterArray.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
 
 CharacterArray initialize!
--- a/Class.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/Class.st	Tue Jun 05 14:35:12 2012 +0100
@@ -21,7 +21,7 @@
 	category:'Kernel-Classes'
 !
 
-Array variableSubclass:#ArrayWithSequenceNumberValidation
+Array subclass:#ArrayWithSequenceNumberValidation
 	instanceVariableNames:'sequenceNumber'
 	classVariableNames:''
 	poolDictionaries:''
@@ -443,8 +443,6 @@
     "Modified: 23.4.1996 / 15:56:58 / cg"
 ! !
 
-
-
 !Class methodsFor:'Compatibility-Dolphin'!
 
 defaultCategoryForDolphinClasses
@@ -627,7 +625,6 @@
     "Created: / 18.6.1998 / 22:08:45 / cg"
 ! !
 
-
 !Class methodsFor:'accessing'!
 
 addChangeRecordForClass:aClass andNotifyChangeOf:aspect
@@ -1342,33 +1339,33 @@
     |classes pivateClassesOf|
 
     classes := self privateClasses.
-    (classes size > 0) ifTrue:[
-	classes := classes asOrderedCollection.
-	classes sort:[:a :b | a name < b name].
-
-	pivateClassesOf := IdentityDictionary new.
-	classes do:[:each | pivateClassesOf at:each put:(each allPrivateClasses)].
-
-	classes topologicalSort:[:a :b |
-	    "/ a must come before b iff:
-	    "/    b is a subclass of a
-	    "/    b has a private class which is a subclass of a
-
-	    |mustComeBefore pivateClassesOfB|
-	    mustComeBefore := b isSubclassOf:a.
-	    pivateClassesOfB := pivateClassesOf at:b.
-	    pivateClassesOfB do:[:eachClassInB |
-		mustComeBefore := mustComeBefore or:[eachClassInB isSubclassOf:a]
-	    ].
-	    mustComeBefore
-	].
+    classes notEmpty ifTrue:[
+        classes := classes asOrderedCollection.
+        classes sort:[:a :b | a name < b name].
+
+        pivateClassesOf := IdentityDictionary new.
+        classes do:[:each | pivateClassesOf at:each put:(each allPrivateClasses)].
+
+        classes topologicalSort:[:a :b |
+            "/ a must come before b iff:
+            "/    b is a subclass of a
+            "/    b has a private class which is a subclass of a
+
+            |mustComeBefore pivateClassesOfB|
+            mustComeBefore := b isSubclassOf:a.
+            pivateClassesOfB := pivateClassesOf at:b.
+            pivateClassesOfB do:[:eachClassInB |
+                mustComeBefore := mustComeBefore or:[eachClassInB isSubclassOf:a]
+            ].
+            mustComeBefore
+        ].
     ].
     ^ classes.
 
     "
      Object privateClassesSorted
-     NewSystemBrowser privateClassesSorted
-     NewSystemBrowser privateClasses
+     Class privateClassesSorted
+     Class privateClasses
     "
 
     "Created: 22.3.1997 / 16:10:42 / cg"
@@ -1592,16 +1589,26 @@
 sharedPools
     "this returns a collection of the real pools (i.e. the PoolDictionaries)"
 
-    |ns pools|
+    |ns ns2 pools|
 
     ns := self nameSpace.
+    ns2 := self topNameSpace.    
     pools :=
          self sharedPoolNames 
             collect:[:eachName | 
                     |pool|
 
                     ns ~= Smalltalk ifTrue:[
-                        pool := ns at:eachName asSymbol.
+                        ns isNameSpace ifTrue:[
+                            pool := ns at:eachName asSymbol.
+                        ] ifFalse:[
+                            pool := ns privateClassesAt:eachName asSymbol.
+                        ]
+                    ].
+                    pool isNil ifTrue:[
+                        ns2 ~= Smalltalk ifTrue:[
+                            pool := ns2 at:eachName asSymbol.
+                        ].
                     ].
                     pool isNil ifTrue:[
                         pool := Smalltalk at:eachName asSymbol.
@@ -1622,7 +1629,7 @@
      Win32OperatingSystem sharedPools
     "
 
-    "Modified: / 07-02-2012 / 16:52:07 / cg"
+    "Modified: / 29-05-2012 / 12:09:27 / cg"
 !
 
 sharedPools:aCollection
@@ -1833,8 +1840,9 @@
     ]
 
     "Modified: / 20.6.1998 / 18:17:37 / cg"
-! !
-
+!
+
+ !
 
 !Class methodsFor:'adding & removing'!
 
@@ -1923,7 +1931,6 @@
     "Modified: 4.6.1997 / 14:48:02 / cg"
 ! !
 
-
 !Class methodsFor:'changes management'!
 
 addChangeRecordForChangeCategory
@@ -3061,26 +3068,26 @@
     aStream nextPutAll:'  <inst-vars>'.
     varNames := self instVarNames.
     varNames size > 0 ifTrue:[
-	aStream cr.
-	varNames do:[:nm |
-	    aStream nextPutAll:'    <name>'.
-	    aStream nextPutAll:nm.
-	    aStream nextPutLine:'</name>'.
-	].
-	aStream nextPutAll:'  '.
+        aStream cr.
+        varNames do:[:nm |
+            aStream nextPutAll:'    <name>'.
+            aStream nextPutAll:nm.
+            aStream nextPutLine:'</name>'.
+        ].
+        aStream nextPutAll:'  '.
     ].
     aStream nextPutLine:'</inst-vars>'.
 
     aStream nextPutAll:'  <class-inst-vars>'.
     varNames := self class instVarNames.
     varNames size > 0 ifTrue:[
-	aStream cr.
-	varNames do:[:nm |
-	    aStream nextPutAll:'    <name>'.
-	    aStream nextPutAll:nm.
-	    aStream nextPutLine:'</name>'.
-	].
-	aStream nextPutAll:'  '.
+        aStream cr.
+        varNames do:[:nm |
+            aStream nextPutAll:'    <name>'.
+            aStream nextPutAll:nm.
+            aStream nextPutLine:'</name>'.
+        ].
+        aStream nextPutAll:'  '.
     ].
     aStream nextPutLine:'</class-inst-vars>'.
 
@@ -3094,18 +3101,15 @@
 
     aStream nextPutLine:'</class>'.
 
-    varNames := self classVarNames.
-    varNames size > 0 ifTrue:[
-	varNames do:[:nm |
-	    aStream nextPutLine:'<static>'.
-	    aStream nextPutAll:' <name>'.
-	    aStream nextPutAll:nm.
-	    aStream nextPutLine:'</name>'.
-	    aStream nextPutAll:' <environment>'.
-	    aStream nextPutAll:self name.
-	    aStream nextPutLine:'</environment>'.
-	    aStream nextPutLine:'</static>'.
-	].
+    self classVarNames do:[:nm |
+        aStream nextPutLine:'<static>'.
+        aStream nextPutAll:' <name>'.
+        aStream nextPutAll:nm.
+        aStream nextPutLine:'</name>'.
+        aStream nextPutAll:' <environment>'.
+        aStream nextPutAll:self name.
+        aStream nextPutLine:'</environment>'.
+        aStream nextPutLine:'</static>'.
     ].
 !
 
@@ -3273,7 +3277,6 @@
     "
 ! !
 
-
 !Class methodsFor:'printOut'!
 
 htmlDocumentation
@@ -3611,7 +3614,8 @@
     "append a category change record to aStream"
 
     self printClassNameOn:aStream.
-    aStream nextPutAll:(' category:' , category storeString).
+    aStream nextPutAll:' category:'.
+    category storeOn:aStream.
     aStream nextPutChunkSeparator.
 
     "Created: 3.12.1995 / 13:43:33 / cg"
@@ -3656,8 +3660,10 @@
 
     "append a class-remove-record to aStream"
 
-    aStream nextPutAll:('Smalltalk removeClass:' , oldClass name).
-    aStream nextPutChunkSeparator.
+    aStream 
+        nextPutAll:'Smalltalk removeClass:';
+        nextPutAll:oldClass name;
+        nextPutChunkSeparator.
 !
 
 addChangeRecordForClassRename:oldName to:newName to:aStream
@@ -3665,10 +3671,15 @@
 
     "append a class-rename-record to aStream"
 
-    aStream nextPutAll:('Smalltalk renameClass:' , oldName, ' to:''' , newName , '''').
-    aStream nextPutChunkSeparator.
-
-    "Modified: 30.10.1996 / 20:27:02 / cg"
+    aStream 
+        nextPutAll:'Smalltalk renameClass:';
+        nextPutAll:oldName;
+        nextPutAll:' to:''';
+        nextPutAll:newName;
+        nextPutAll:'''';
+        nextPutChunkSeparator.
+
+    "Modified: / 01-06-2012 / 09:44:04 / cg"
 !
 
 addChangeRecordForPrimitiveDefinitions:aClass to:aStream
@@ -3825,18 +3836,18 @@
     |clsPkg|
 
     clsPkg := self package.
-    aPackageID = clsPkg ifTrue:[^ #()].
+    aPackageID = clsPkg ifTrue:[^ false].
 
     self instAndClassMethodsDo:[:mthd |
-	mthd package = aPackageID ifTrue:[ ^ true].
+        mthd package = aPackageID ifTrue:[ ^ true].
     ].
     ^ false
 
     "
      Smalltalk allClasses
-	select:[:each | each hasExtensionsFrom:'stx:goodies/refactyBrowser']
+        select:[:each | each hasExtensionsFrom:'stx:goodies/refactyBrowser']
      Smalltalk allClasses
-	select:[:each | each hasExtensionsFrom:'stx:libboss']
+        select:[:each | each hasExtensionsFrom:'stx:libboss']
     "
 
     "Modified: / 06-03-2007 / 11:55:39 / cg"
@@ -4324,19 +4335,19 @@
     (owner := self owningClass) notNil ifTrue:[^ owner findVersionMethodOfManager:aSourceCodemanagerOrNil].
 
     tryVersionFromVersionMethod :=
-	[:versionMethodsName |
-	    |aVersionMethod val|
-
-	    aVersionMethod := meta compiledMethodAt:versionMethodsName.
-	    (aVersionMethod notNil and:[aVersionMethod isExecutable]) ifTrue:[
-		"/
-		"/ if it's a method returning the version string,
-		"/ that's the returned value
-		"/
-		val := cls perform:versionMethodsName.
-		val isString ifTrue:[^ aVersionMethod].
-	    ].
-	].
+        [:versionMethodsName |
+            |aVersionMethod val|
+
+            aVersionMethod := meta compiledMethodAt:versionMethodsName.
+            (aVersionMethod notNil and:[aVersionMethod isExecutable]) ifTrue:[
+                "/
+                "/ if it's a method returning the version string,
+                "/ that's the returned value
+                "/
+                val := cls perform:versionMethodsName.
+                val isString ifTrue:[^ aVersionMethod].
+            ].
+        ].
 
     meta := self theMetaclass.
     cls := self theNonMetaclass.
@@ -4344,16 +4355,16 @@
     allVersionMethodNames := meta methodDictionary keys select:[:sel | sel startsWith:AbstractSourceCodeManager prefixOfVersionMethodSelector].
 
     aSourceCodemanagerOrNil notNil ifTrue:[
-	nameOfVersionMethodForManager := aSourceCodemanagerOrNil nameOfVersionMethodInClasses.
-	(allVersionMethodNames includes:nameOfVersionMethodForManager) ifTrue:[
-	    tryVersionFromVersionMethod value:nameOfVersionMethodForManager
-	].
-
-	"/ only trust the oldVersion method, iff there is no other scv-version
-	"/ (i.e. do not misuse an svn-checked-in #version as a version_cvs)
-	(allVersionMethodNames copyWithout:nameOfVersionMethodForManager) size > 0 ifTrue:[
-	    ^ nil
-	].
+        nameOfVersionMethodForManager := aSourceCodemanagerOrNil nameOfVersionMethodInClasses.
+        (allVersionMethodNames includes:nameOfVersionMethodForManager) ifTrue:[
+            tryVersionFromVersionMethod value:nameOfVersionMethodForManager
+        ].
+
+        "/ only trust the oldVersion method, iff there is no other scv-version
+        "/ (i.e. do not misuse an svn-checked-in #version as a version_cvs)
+        (allVersionMethodNames copyWithout:nameOfVersionMethodForManager) notEmpty ifTrue:[
+            ^ nil
+        ].
     ].
 
     nameOfOldVersionMethod := self nameOfOldVersionMethod.
@@ -4363,7 +4374,7 @@
 
     "
      Smalltalk allClassesDo:[:cls |
-	Transcript show:cls name; show:' -> '; showCR:cls findVersionMethod
+        Transcript show:cls name; show:' -> '; showCR:cls findVersionMethod
      ].
 
      Number findVersionMethod
@@ -4538,11 +4549,11 @@
      (this is done for backward compatibility,)
 
      For example:
-	'....(libbasic)'                         -> module: stx directory: libbasic library: libbasic
-	'....(stx:libbasic)'                     -> module: stx directory: libbasic library: libbasic
-	'....(stx:foo:libbfoo)'                  -> module: stx directory: foo library: libfoo
-	'....(aeg:libIECInterface)'              -> module: aeg directory: libIECInterface library:libIECInterface
-	'....(stx:goodies/persistency:libdbase)' -> module: stx directory: goodies/persistency library:libdbase
+        '....(libbasic)'                         -> module: stx directory: libbasic library: libbasic
+        '....(stx:libbasic)'                     -> module: stx directory: libbasic library: libbasic
+        '....(stx:foo:libbfoo)'                  -> module: stx directory: foo library: libfoo
+        '....(aeg:libIECInterface)'              -> module: aeg directory: libIECInterface library:libIECInterface
+        '....(stx:goodies/persistency:libdbase)' -> module: stx directory: goodies/persistency library:libdbase
 
      The way how the sourceCodeManager uses this to find the source location
      depends on the scheme used. For CVS, the module is taken as the -d arg,
@@ -4550,7 +4561,7 @@
      Other schemes may do things differently - these are not yet specified.
 
      Caveat:
-	Encoding this info in the package string seems somewhat kludgy.
+        Encoding this info in the package string seems somewhat kludgy.
     "
 
     |owner sourceInfo packageString idx1 idx2
@@ -4564,90 +4575,89 @@
     packageString := package asString.
     idx1 := packageString lastIndexOf:$(.
     idx1 ~~ 0 ifTrue:[
-	idx2 := packageString indexOf:$) startingAt:idx1+1.
-	idx2 ~~ 0 ifTrue:[
-	    sourceInfo := packageString copyFrom:idx1 + 1 to:idx2 - 1
-	]
+        idx2 := packageString indexOf:$) startingAt:idx1+1.
+        idx2 ~~ 0 ifTrue:[
+            sourceInfo := packageString copyFrom:idx1 + 1 to:idx2 - 1
+        ]
     ] ifFalse:[
-	sourceInfo := packageString
+        sourceInfo := packageString
     ].
 
     sourceInfo isNil ifTrue:[^ nil].
     components := sourceInfo asCollectionOfSubstringsSeparatedBy:$:.
-    components size == 0 ifTrue:[
+    components notEmpty ifTrue:[
 "/        moduleString := 'stx'.
 "/        directoryString := libraryString := ''.
-	^ nil
+        ^ nil
     ].
 
     component1 := components at:1.
     components size == 1 ifTrue:[
-	"/ a single name given - the module becomes 'stx' or
-	"/ the very first directory component (if such a module exists).
-	"/ If the component includes slashes, its the directory
-	"/ otherwise the library.
-	"/
-	dirComponents := Filename components:component1.
-	(dirComponents size > 1
-	and:[(mgr := self sourceCodeManager) notNil
-	and:[mgr checkForExistingModule:dirComponents first]]) ifTrue:[
-	    moduleString := dirComponents first.
-	    directoryString := libraryString := (Filename fromComponents:(dirComponents copyFrom:2)) asString.
-	] ifFalse:[
-	    "/ non-existing; assume directory under the stx package.
-	    moduleString := 'stx'.
-	    (component1 startsWith:'stx/') ifTrue:[
-		component1 := component1 copyFrom:5
-	    ].
-	    directoryString := libraryString := component1.
-	].
-
-	(libraryString includes:$/) ifTrue:[
-	    libraryString := libraryString asFilename baseName
-	]
+        "/ a single name given - the module becomes 'stx' or
+        "/ the very first directory component (if such a module exists).
+        "/ If the component includes slashes, its the directory
+        "/ otherwise the library.
+        "/
+        dirComponents := Filename components:component1.
+        (dirComponents size > 1
+        and:[(mgr := self sourceCodeManager) notNil
+        and:[mgr checkForExistingModule:dirComponents first]]) ifTrue:[
+            moduleString := dirComponents first.
+            directoryString := libraryString := (Filename fromComponents:(dirComponents copyFrom:2)) asString.
+        ] ifFalse:[
+            "/ non-existing; assume directory under the stx package.
+            moduleString := 'stx'.
+            (component1 startsWith:'stx/') ifTrue:[
+                component1 := component1 copyFrom:5
+            ].
+            directoryString := libraryString := component1.
+        ].
+
+        (libraryString includes:$/) ifTrue:[
+            libraryString := libraryString asFilename baseName
+        ]
     ] ifFalse:[
-	component2 := components at:2.
-	components size == 2 ifTrue:[
-	    "/ two components - assume its the module and the directory;
-	    "/ the library is assumed to be named after the directory
-	    "/ except, if slashes are in the name; then the libraryname
-	    "/ is the last component.
-	    "/
-	    moduleString := component1.
-	    directoryString := libraryString := component2.
-	    (libraryString includes:$/) ifTrue:[
-		libraryString := libraryString asFilename baseName
-	    ]
-	] ifFalse:[
-	    "/ all components given
-	    moduleString := component1.
-	    directoryString := component2.
-	    libraryString := components at:3.
-	]
+        moduleString := component1.
+        component2 := components at:2.
+        directoryString := component2.
+        components size == 2 ifTrue:[
+            "/ two components - assume its the module and the directory;
+            "/ the library is assumed to be named after the directory
+            "/ except, if slashes are in the name; then the libraryname
+            "/ is the last component.
+            "/
+            libraryString := component2.
+            (libraryString includes:$/) ifTrue:[
+                libraryString := libraryString asFilename baseName
+            ]
+        ] ifFalse:[
+            "/ all components given
+            libraryString := components at:3.
+        ]
     ].
 
     libraryString isEmpty ifTrue:[
-	directoryString notEmpty ifTrue:[
-	    libraryString := directoryString asFilename baseName
-	].
-	libraryString isEmpty ifTrue:[
-	    "/ lets extract the library from the liblist file ...
-	    libraryString := Smalltalk libraryFileNameOfClass:self.
-	    libraryString isNil ifTrue:[^ nil].
-	]
+        directoryString notEmpty ifTrue:[
+            libraryString := directoryString asFilename baseName
+        ].
+        libraryString isEmpty ifTrue:[
+            "/ lets extract the library from the liblist file ...
+            libraryString := Smalltalk libraryFileNameOfClass:self.
+            libraryString isNil ifTrue:[^ nil].
+        ]
     ].
 
     moduleString isEmpty ifTrue:[
-	moduleString := 'stx'.
+        moduleString := 'stx'.
     ].
     directoryString isEmpty ifTrue:[
-	directoryString := libraryString.
+        directoryString := libraryString.
     ].
 
     ^ IdentityDictionary
-	with:(#module->moduleString)
-	with:(#directory->directoryString)
-	with:(#library->libraryString)
+        with:(#module->moduleString)
+        with:(#directory->directoryString)
+        with:(#library->libraryString)
 
     "
      Object packageSourceCodeInfo
@@ -5093,7 +5103,7 @@
                 |f classes|
 
                 sourceStream isNil ifTrue:[
-                    (classes := h classes) size > 0 ifTrue:[
+                    (classes := h classes) notEmptyOrNil ifTrue:[
                         (classes includes:self) ifTrue:[
                             f := h pathName.
                             f := f asFilename directory.
@@ -5535,13 +5545,13 @@
 !Class class methodsFor:'documentation'!
 
 version
-    ^ '$Id: Class.st 10798 2012-03-29 20:59:07Z vranyj1 $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Class.st,v 1.605 2012/06/01 10:45:53 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Class.st,v 1.602 2012/02/07 16:41:55 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/Class.st,v 1.605 2012/06/01 10:45:53 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Class.st 10798 2012-03-29 20:59:07Z vranyj1 $'
+    ^ '$ Id: Class.st 10643 2011-06-08 21:53:07Z vranyj1  $'
 ! !
--- a/CompiledCode.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/CompiledCode.st	Tue Jun 05 14:35:12 2012 +0100
@@ -562,7 +562,7 @@
 
 programmingLanguage
 "/ the following is correct, but might be too slow...
-"/ we have language-specific methods anyway, so simply ask itself.
+"/ we have language-specific methods anyway, so simply redefine there.
 "/    |mclass|
 "/
 "/    mclass := self mclass.
@@ -573,6 +573,8 @@
     "
      (Object compiledMethodAt:#at:) parserClass
     "
+
+    "Modified (comment): / 01-06-2012 / 21:10:56 / cg"
 !
 
 syntaxHighlighterClass
@@ -1835,15 +1837,15 @@
 !CompiledCode class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CompiledCode.st,v 1.114 2012/03/26 17:02:56 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CompiledCode.st,v 1.115 2012/06/01 21:36:35 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/CompiledCode.st,v 1.114 2012/03/26 17:02:56 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/CompiledCode.st,v 1.115 2012/06/01 21:36:35 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: CompiledCode.st 10804 2012-04-13 13:18:13Z vranyj1 $'
+    ^ '$Id: CompiledCode.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
 
 
--- a/Context.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/Context.st	Tue Jun 05 14:35:12 2012 +0100
@@ -514,7 +514,7 @@
     "/.
     method notNil ifTrue:[
         method isMethod ifTrue:[
-            method wrapper isNil ifTrue:[
+            true "method wrapper isNil" ifTrue:[
                 ^ method
             ]
         ]
@@ -563,7 +563,7 @@
     ^ nil
 
     "Modified: / 28-06-2011 / 20:23:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 01-07-2011 / 09:39:45 / cg"
+    "Modified: / 31-05-2012 / 11:54:34 / cg"
 !
 
 methodClass
@@ -2434,11 +2434,11 @@
 !Context class methodsFor:'documentation'!
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Context.st,v 1.168 2012/03/07 12:19:05 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/Context.st,v 1.169 2012/05/31 16:32:02 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Context.st 10792 2012-03-21 17:45:38Z vranyj1 $'
+    ^ '$Id: Context.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
 
 Context initialize!
--- a/Method.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/Method.st	Tue Jun 05 14:35:12 2012 +0100
@@ -569,11 +569,12 @@
      from the methods source (excluding any double-quotes).
      Returns nil if there is no comment (or source is not available)."
 
-    |src|
+    |src parserClass|
 
     src := self source.
     src isNil ifTrue:[^ nil].
-    ^ self programmingLanguage parserClass methodCommentFromSource:src
+    (parserClass := self programmingLanguage parserClass) isNil ifTrue:[^ nil].
+    ^ parserClass methodCommentFromSource:src
 
     "
      (Method compiledMethodAt:#comment) comment
@@ -581,7 +582,7 @@
     "
 
     "Modified: / 23-02-1998 / 10:26:08 / stefan"
-    "Modified: / 17-07-2010 / 14:23:56 / cg"
+    "Modified: / 01-06-2012 / 23:03:57 / cg"
 !
 
 getPackage
@@ -3631,15 +3632,15 @@
 !Method class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.383 2012/04/04 13:57:45 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.384 2012/06/01 21:16:28 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/Method.st,v 1.383 2012/04/04 13:57:45 stefan Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/Method.st,v 1.384 2012/06/01 21:16:28 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: Method.st 10804 2012-04-13 13:18:13Z vranyj1 $'
+    ^ '$Id: Method.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
 
 Method initialize!
--- a/ProgrammingLanguage.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/ProgrammingLanguage.st	Tue Jun 05 14:35:12 2012 +0100
@@ -466,6 +466,12 @@
     ^ nil
 !
 
+parenthesisSpecificationForEditor
+    ^ TextView defaultParenthesisSpecification
+
+    "Created: / 01-06-2012 / 22:52:25 / cg"
+!
+
 writeComment:aStringOrStringCollection on:aStream 
     "Utility method - writes a comment to a stream,
      using proper syntax"
@@ -480,11 +486,11 @@
 !ProgrammingLanguage class methodsFor:'documentation'!
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/ProgrammingLanguage.st,v 1.16 2011/11/19 10:23:29 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/ProgrammingLanguage.st,v 1.17 2012/06/01 21:13:26 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: ProgrammingLanguage.st 10781 2012-02-18 23:08:56Z vranyj1 $'
+    ^ '$Id: ProgrammingLanguage.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
 
 ProgrammingLanguage initialize!
--- a/SequenceableCollection.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/SequenceableCollection.st	Tue Jun 05 14:35:12 2012 +0100
@@ -380,7 +380,6 @@
     ^ self == SequenceableCollection
 ! !
 
-
 !SequenceableCollection methodsFor:'Compatibility-Squeak'!
 
 allButFirst
@@ -655,13 +654,32 @@
     "Created: / 22-10-2008 / 21:25:35 / cg"
 ! !
 
+!SequenceableCollection methodsFor:'Compatibility-V''Age'!
+
+replaceFrom:start to:end withObject:anObject
+    "Replace the elements from start to end with anObject.
+     Return the receiver."
+
+    self from:start to:end put:anObject.
+    ^ self.
+
+    "
+     |a|
+
+     a := Array new: 10.
+     a replaceFrom:3 to:7 withObject:999.
+     a
+    "
+
+    "Created: / 16-05-2012 / 11:13:55 / cg"
+! !
+
 !SequenceableCollection methodsFor:'Compatibility-VW'!
 
 replaceElementsFrom:start to:stop withArray:anArray startingAt:repStart
     ^ self replaceFrom:start to:stop with:anArray startingAt:repStart
 ! !
 
-
 !SequenceableCollection methodsFor:'accessing'!
 
 after:anObject
@@ -4208,6 +4226,19 @@
     "Created: / 30.1.2000 / 01:02:28 / cg"
 !
 
+from:start conform:aOneArgBlock
+    "return true, if the elements starting at the start-index conform to some condition.
+     I.e. return false, if aBlock returns false for any of those elements;
+     true otherwise."
+
+    self from:start to:(self size) do:[:element | 
+        (aOneArgBlock value:element) ifFalse:[^ false]
+    ].
+    ^ true
+
+    "Created: / 25-05-2012 / 14:02:13 / cg"
+!
+
 from:startIndex do:aBlock
     "evaluate the argument, aBlock for the elements starting with the
      element at startIndex to the end."
@@ -4282,6 +4313,27 @@
     "
 !
 
+from:start to:end conform:aOneArgBlock
+    "return true, if the elements from start-index to end-index conform to some condition.
+     I.e. return false, if aBlock returns false for any of those elements;
+     true otherwise."
+
+    self from:start to:end do:[:element | 
+        (aOneArgBlock value:element) ifFalse:[^ false]
+    ].
+    ^ true
+
+    "
+     #(1 2 3 4 5) from:2 to:2 conform:[:el | el even]     
+     #(1 2 2 4 5) from:2 to:4 conform:[:el | el even]               
+     #(1 2 2 4 5) from:2 to:5 conform:[:el | el even]               
+     #(2 4 6 8 10) conform:[:el | el even]    
+    "
+
+    "Modified: / 13-09-2006 / 11:19:03 / cg"
+    "Created: / 25-05-2012 / 14:00:50 / cg"
+!
+
 from:index1 to:index2 do:aBlock
     "evaluate the argument, aBlock for the elements with index index1 to
      index2 in the collection"
@@ -6519,7 +6571,6 @@
     "Created: 14.2.1997 / 16:13:03 / cg"
 ! !
 
-
 !SequenceableCollection methodsFor:'searching'!
 
 detect:aBlock startingAt:startIndex
@@ -7009,26 +7060,27 @@
 indexOf:elementToFind replaceWith:replacement startingAt:start stoppingAt:stop
     "search for the first occurrence of elementToFind starting at start,
      stopping the search at stop. If found, replace the element by replacement
-     and return the index.
-     If not found, return 0."
+     and return the index. If not found, return 0.
+     The comparison is done using =
+     (i.e. equality test - not identity test)."
 
     |idx|
 
     idx := self indexOf:elementToFind startingAt:start.
     ((idx > 0) and:[idx <= stop]) ifTrue:[
-	self at:idx put:replacement.
-	^ idx
+        self at:idx put:replacement.
+        ^ idx
     ].
     ^ 0
 
     "
      args:    elementToFind : <object>
-	      replacement   : <integer>
-	      start         : <integer>
-	      stop          : <integer>
+              replacement   : <integer>
+              start         : <integer>
+              stop          : <integer>
 
      returns: elementIndex - if found (and replaced)
-	      0            - if not found
+              0            - if not found
     "
 
     "
@@ -7039,7 +7091,8 @@
      a printNL.
     "
 
-    "Modified: / 20.5.1998 / 14:59:30 / cg"
+    "Modified: / 20-05-1998 / 14:59:30 / cg"
+    "Modified (comment): / 23-05-2012 / 13:29:18 / cg"
 !
 
 indexOf:anElement startingAt:start
@@ -7315,8 +7368,7 @@
 nextIndexOf:anElement from:start to:stop ifAbsent:exceptionBlock
     "search the collection for anElement, starting the search at index start
      and stopping at stop;
-     if found, return the index otherwise return the value of the
-     exceptionBlock.
+     if found, return the index otherwise return the value of the exceptionBlock.
      The comparison is done using =
      (i.e. equality test - not identity test)."
 
@@ -7343,6 +7395,7 @@
     "
 
     "Modified: / 23-09-2011 / 14:03:36 / cg"
+    "Modified (comment): / 23-05-2012 / 13:29:42 / cg"
 !
 
 prevIndexOf:anElement from:startSearchIndex to:endSearchIndex
@@ -7555,8 +7608,8 @@
     "search the collection for anElement, starting the search at index start;
      ending at stop.
      If found (within the range), return the index, otherwise return 0.
-     The comparison is done using =
-     (i.e. equality test - not identity test)."
+     The comparison is done using ==
+     (i.e. identity test - not equality test)."
 
     |startIndex "{ Class: SmallInteger }"
      stopIndex  "{ Class: SmallInteger }" |
@@ -7564,21 +7617,22 @@
     startIndex := start.
     stopIndex := self size min:stop.
     startIndex to:stopIndex do:[:index |
-	anElement == (self at:index) ifTrue:[^ index].
+        anElement == (self at:index) ifTrue:[^ index].
     ].
     ^ 0
 
     "
      args:    anElement : <object>
-	      start     : <integer>
-	      stop      : <integer>
+              start     : <integer>
+              stop      : <integer>
 
      returns: elementIndex - if found
-	      0            - if not found
-    "
-
-    "Created: / 12.4.1996 / 18:23:07 / cg"
-    "Modified: / 20.5.1998 / 15:00:50 / cg"
+              0            - if not found
+    "
+
+    "Created: / 12-04-1996 / 18:23:07 / cg"
+    "Modified: / 20-05-1998 / 15:00:50 / cg"
+    "Modified (comment): / 23-05-2012 / 13:28:21 / cg"
 !
 
 identityIndexOf:anElement startingAt:start ifAbsent:exceptionBlock
@@ -8644,12 +8698,16 @@
 
 !SequenceableCollection class methodsFor:'documentation'!
 
+version
+    ^ '$Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.322 2012/05/25 12:10:28 cg Exp $'
+!
+
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.318 2012/04/20 15:19:12 stefan Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.322 2012/05/25 12:10:28 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: SequenceableCollection.st 10807 2012-05-05 21:58:24Z vranyj1 $'
+    ^ '$Id: SequenceableCollection.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
 
 SequenceableCollection initialize!
--- a/String.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/String.st	Tue Jun 05 14:35:12 2012 +0100
@@ -11,7 +11,7 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-CharacterArray variableByteSubclass:#String
+CharacterArray subclass:#String
 	instanceVariableNames:''
 	classVariableNames:'CRLF LF'
 	poolDictionaries:''
@@ -44,55 +44,6 @@
 %}
 ! !
 
-!String primitiveFunctions!
-%{
-
-static int
-nextOnKeyboard(char1, char2)
-{
-    /* compare two characters if they are next to each other on a (US-) keyboard */
-
-    static char *us_keys[] = { "1234567890-",
-			    "*qwertyuiop",
-			    "**asdfghjkl:",
-			    "***zxcvbnm",
-			    0 };
-    static char *de_keys[] = { "1234567890-",
-			    "*qwertzuiop",
-			    "**asdfghjkl:",
-			    "***yxcvbnm",
-			    0 };
-    char **keys = us_keys;
-    char **line1, **line2;
-    char *col1, *col2;
-    int diff;
-
-    for (line1 = keys; *line1 != 0; line1++) {
-	for (col1 = *line1; *col1 != 0 && *col1 != char1; col1++)
-	    continue;
-    }
-    if (*col1 == 0)
-	return(0);
-
-    for (line2 = keys; *line2 != 0; line2++) {
-	for (col2 = *line2; *col2 != 0 && *col2 != char2; col2++)
-	    continue;
-    }
-    if (*col2 == 0)
-	return(0);
-
-    diff = col1 - col2;
-    if (diff > 1 || diff < -1)
-	return(0);
-
-    diff = line1 - line2;
-    if (diff > 1 || diff < -1)
-	return(0);
-    return(1);
-}
-%}
-! !
-
 !String class methodsFor:'documentation'!
 
 copyright
@@ -473,10 +424,10 @@
     stringSize := aString size.
     hash := speciesHash bitAnd: 16rFFFFFFF.
     1 to: stringSize do: [:pos |
-        hash := hash + (aString at: pos) asInteger.
-        "Begin hashMultiply"
-        low := hash bitAnd: 16383.
-        hash := (16r260D * low + ((16r260D * (hash bitShift: -14) + (16r0065 * low) bitAnd: 16383) * 16384)) bitAnd: 16r0FFFFFFF.
+	hash := hash + (aString at: pos) asInteger.
+	"Begin hashMultiply"
+	low := hash bitAnd: 16383.
+	hash := (16r260D * low + ((16r260D * (hash bitShift: -14) + (16r0065 * low) bitAnd: 16383) * 16384)) bitAnd: 16r0FFFFFFF.
     ].
     ^ hash.
 !
@@ -691,11 +642,11 @@
     cls = __qClass(slf);
     indx = 0;
     if (cls != String) {
-        if (indx < 0) goto badIndex;
-        indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+	if (indx < 0) goto badIndex;
+	indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
     }
     if ((unsigned)indx < (unsigned)(__stringSize(slf))) {
-        RETURN ( __MKCHARACTER(__stringVal(slf)[indx] & 0xFF) );
+	RETURN ( __MKCHARACTER(__stringVal(slf)[indx] & 0xFF) );
     }
 badIndex: ;
 %}.
@@ -756,40 +707,40 @@
     OBJ cls;
 
     if (__isStringLike(aCollection)) {
-        matchP = __stringVal(aCollection);
-        cp = __stringVal(self);
-        if ((cls = __qClass(self)) != String)
-            cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-
-        switch (__stringSize(aCollection)) {
-            case 3:
-                /* three character search */
-                if (strchr(cp, matchP[2])) {
-                    RETURN ( true );
-                }
-                /* fall into */
-            case 2:
-                /* two character search */
-                if (strchr(cp, matchP[1])) {
-                    RETURN ( true );
-                }
-                /* fall into */
-            case 1:
-                /* single character search */
-                if (strchr(cp, matchP[0])) {
-                    RETURN ( true );
-                }
-                /* fall into */
-            case 0:
-                RETURN ( false );
-        }
-        while (*cp) {
-            if (strchr(matchP, *cp)) {
-                RETURN ( true );
-            }
-            cp++;
-        }
-        RETURN ( false );
+	matchP = __stringVal(aCollection);
+	cp = __stringVal(self);
+	if ((cls = __qClass(self)) != String)
+	    cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+
+	switch (__stringSize(aCollection)) {
+	    case 3:
+		/* three character search */
+		if (strchr(cp, matchP[2])) {
+		    RETURN ( true );
+		}
+		/* fall into */
+	    case 2:
+		/* two character search */
+		if (strchr(cp, matchP[1])) {
+		    RETURN ( true );
+		}
+		/* fall into */
+	    case 1:
+		/* single character search */
+		if (strchr(cp, matchP[0])) {
+		    RETURN ( true );
+		}
+		/* fall into */
+	    case 0:
+		RETURN ( false );
+	}
+	while (*cp) {
+	    if (strchr(matchP, *cp)) {
+		RETURN ( true );
+	    }
+	    cp++;
+	}
+	RETURN ( false );
     }
 %}.
     ^ super includesAny:aCollection
@@ -827,92 +778,92 @@
     OBJ cls;
 
     if (__isSmallInteger(start)) {
-        index = __intVal(start);
-        if (index > 0) {
-            if (__isCharacter(aCharacter)) {
-                byteValue = __intVal(_characterVal(aCharacter));
-                if (byteValue <= 0xFF) {
-                    last = __stringSize(self);
-                    cp = __stringVal(self);
-                    if ((cls = __qClass(self)) != String) {
-                        int numInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-
-                        cp += numInstBytes;
-                        last += numInstBytes;
-                    }
-                    if (index <= last) {
-#ifdef FAST_MEMCHR    
-                        ncp = (unsigned char *) memchr(cp+index-1, byteValue, last+1-index);
-                        if (ncp) {
-                            RETURN ( __mkSmallInteger(ncp - cp + 1) );
-                        }
+	index = __intVal(start);
+	if (index > 0) {
+	    if (__isCharacter(aCharacter)) {
+		byteValue = __intVal(_characterVal(aCharacter));
+		if (byteValue <= 0xFF) {
+		    last = __stringSize(self);
+		    cp = __stringVal(self);
+		    if ((cls = __qClass(self)) != String) {
+			int numInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+
+			cp += numInstBytes;
+			last += numInstBytes;
+		    }
+		    if (index <= last) {
+#ifdef FAST_MEMCHR
+			ncp = (unsigned char *) memchr(cp+index-1, byteValue, last+1-index);
+			if (ncp) {
+			    RETURN ( __mkSmallInteger(ncp - cp + 1) );
+			}
 #else
 # ifdef __UNROLL_LOOPS__
-                        {
-                            int last3 = last-3;
-
-                            for (; index <= last3; index += 4) {
-                                if (cp[index-1] == byteValue) { RETURN ( __mkSmallInteger(index) ); }
-                                if (cp[index-1+1] == byteValue) { RETURN ( __mkSmallInteger(index+1) ); }
-                                if (cp[index-1+2] == byteValue) { RETURN ( __mkSmallInteger(index+2) ); }
-                                if (cp[index-1+3] == byteValue) { RETURN ( __mkSmallInteger(index+3) ); }
-                            }
-                        }
+			{
+			    int last3 = last-3;
+
+			    for (; index <= last3; index += 4) {
+				if (cp[index-1] == byteValue) { RETURN ( __mkSmallInteger(index) ); }
+				if (cp[index-1+1] == byteValue) { RETURN ( __mkSmallInteger(index+1) ); }
+				if (cp[index-1+2] == byteValue) { RETURN ( __mkSmallInteger(index+2) ); }
+				if (cp[index-1+3] == byteValue) { RETURN ( __mkSmallInteger(index+3) ); }
+			    }
+			}
 # endif
 # ifdef V1
-                        for (; index <= last; index++) {
-                            if (cp[index-1] == byteValue) {
-                                RETURN ( __mkSmallInteger(index) );
-                            }
-                        }
+			for (; index <= last; index++) {
+			    if (cp[index-1] == byteValue) {
+				RETURN ( __mkSmallInteger(index) );
+			    }
+			}
 # endif
 # ifdef V2
-                        {
-                            // see bit twiddling hacks
+			{
+			    // see bit twiddling hacks
 #                           define hasZeroByte(v) (((v) - 0x01010101UL) & ~(v) & 0x80808080UL)
 #                           define hasByteM(v,m)   hasZeroByte( (v) ^ m)
 
-                            // the following loop checks four bytes at once
-                            if (((index-1) & 0x3) == 0) {
-                                int last4 = last-4;
-                                int m = (~0UL/255 * (byteValue));
-
-                                while (index <= last4) {
-                                    unsigned int v = *(unsigned int *)(cp+index-1);
-
-                                    if (hasByteM(v,m)) break;
-                                    index += 4;
-                                }
-                            }
-                            while (index <= last) {
-                                if (cp[index-1] == byteValue) {
-                                    RETURN ( __mkSmallInteger(index) );
-                                }
-                                index++;
-                            }
-                        }
+			    // the following loop checks four bytes at once
+			    if (((index-1) & 0x3) == 0) {
+				int last4 = last-4;
+				int m = (~0UL/255 * (byteValue));
+
+				while (index <= last4) {
+				    unsigned int v = *(unsigned int *)(cp+index-1);
+
+				    if (hasByteM(v,m)) break;
+				    index += 4;
+				}
+			    }
+			    while (index <= last) {
+				if (cp[index-1] == byteValue) {
+				    RETURN ( __mkSmallInteger(index) );
+				}
+				index++;
+			    }
+			}
 # endif
 #endif
-                    }
-                }
-            }
-            RETURN ( __mkSmallInteger(0) );
-        }
+		    }
+		}
+	    }
+	    RETURN ( __mkSmallInteger(0) );
+	}
     }
 #undef V2
 %}.
     ^ super indexOf:aCharacter startingAt:start
 
     "
-     'hello world' indexOf:$0 startingAt:1   
-     'hello world' indexOf:$l startingAt:1   
-     'hello world' indexOf:$l startingAt:5   
-     'hello world' indexOf:$d startingAt:5   
-     #[0 0 1 0 0] asString indexOf:(Character value:1) startingAt:1  
+     'hello world' indexOf:$0 startingAt:1
+     'hello world' indexOf:$l startingAt:1
+     'hello world' indexOf:$l startingAt:5
+     'hello world' indexOf:$d startingAt:5
+     #[0 0 1 0 0] asString indexOf:(Character value:1) startingAt:1
      #[0 0 1 0 0] asString indexOf:(Character value:0) startingAt:3
 
-     '1234567890123456a' indexOf:$a      
-     '1234567890123456a' indexOf:$b      
+     '1234567890123456a' indexOf:$a
+     '1234567890123456a' indexOf:$b
 
      |s|
      s := '12345678901234b'.
@@ -923,7 +874,7 @@
      self assert:(s indexOf:$4) == 4.
      self assert:(s indexOf:$5) == 5.
      self assert:(s indexOf:$0) == 10.
-     self assert:(s indexOf:$b) == 15.   
+     self assert:(s indexOf:$b) == 15.
 
      |s|
      s := ''.
@@ -992,21 +943,21 @@
      self assert:(s indexOf:$9) == 9.
 
      self assert:(s indexOf:$0) == 0.
-     self assert:(s indexOf:$b) == 0.   
+     self assert:(s indexOf:$b) == 0.
 
      |s|
      s := String new:1024.
      s atAllPut:$a.
      s at:512 put:(Character space).
      Time millisecondsToRun:[
-        1000000 timesRepeat:[ s indexOf:(Character space) ]
-     ]         
+	1000000 timesRepeat:[ s indexOf:(Character space) ]
+     ]
 
      timing (ms):
-        v1: 1763 normal   
-            2340 +unroll   
-            3308 memsrch !!
-        v2: 1045
+	v1: 1763 normal
+	    2340 +unroll
+	    3308 memsrch !!
+	v2: 1045
     "
 
     "Modified: / 10-01-2012 / 17:09:34 / cg"
@@ -1029,76 +980,76 @@
 
     if (__isSmallInteger(start)
      && __isStringLike(aCollectionOfCharacters)) {
-        matchP = __stringVal(aCollectionOfCharacters);
-        index = __intVal(start);
-        if (index > 0) {
-            cp = __stringVal(self) + index - 1;
-            if ((cls = __qClass(self)) != String) {
-                cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-            }
-            len = __stringSize(self);
-            if (index <= len) {
-
-                if (matchP[0] == 0) {
-                    /* matchSet is empty */
-                    RETURN ( __mkSmallInteger(0) );
-                }
-
-                if (matchP[1] == 0) {
-                    /* only a single character match */
-                    unsigned char m = matchP[0];
+	matchP = __stringVal(aCollectionOfCharacters);
+	index = __intVal(start);
+	if (index > 0) {
+	    cp = __stringVal(self) + index - 1;
+	    if ((cls = __qClass(self)) != String) {
+		cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+	    }
+	    len = __stringSize(self);
+	    if (index <= len) {
+
+		if (matchP[0] == 0) {
+		    /* matchSet is empty */
+		    RETURN ( __mkSmallInteger(0) );
+		}
+
+		if (matchP[1] == 0) {
+		    /* only a single character match */
+		    unsigned char m = matchP[0];
 
     #ifdef FAST_MEMCHR
-                    ccp = (unsigned char *) memchr(cp, m, len+1-index);
-                    if (ccp) {
-                        RETURN ( __mkSmallInteger((ccp - cp) + index + 1) );
-                    }
+		    ccp = (unsigned char *) memchr(cp, m, len+1-index);
+		    if (ccp) {
+			RETURN ( __mkSmallInteger((ccp - cp) + index + 1) );
+		    }
     #else
-                    while (c = *cp++) {
-                        if (c == m) {
-                            RETURN ( __mkSmallInteger(index) );
-                        }
-                        index++;
-                    }
+		    while (c = *cp++) {
+			if (c == m) {
+			    RETURN ( __mkSmallInteger(index) );
+			}
+			index++;
+		    }
     #endif
-                    RETURN ( __mkSmallInteger(0) );
-                }
-
-                if (matchP[2] == 0) {
-                    /* two character matches */
-                    unsigned char m1 = matchP[0];
-                    unsigned char m2 = matchP[1];
-
-                    while (c = *cp++) {
-                        if ((c == m1) || (c == m2)) {
-                            RETURN ( __mkSmallInteger(index) );
-                        }
-                        index++;
-                    }
-                    RETURN ( __mkSmallInteger(0) );
-                }
-
-                min = max = matchP[0];
-
-                for (ccp = matchP+1; *ccp ; ccp++) {
-                    unsigned char c = *ccp;
-                    if (c < min) min = c;
-                    else if (c > max) max = c;
-                }
-
-                while (c = *cp++) {
-                    if ((c >= min) && (c <= max)) {
-                        for (ccp = matchP; *ccp ; ccp++) {
-                            if (*ccp == c) {
-                                RETURN ( __mkSmallInteger(index) );
-                            }
-                        }
-                    }
-                    index++;
-                }
-            }
-            RETURN ( __mkSmallInteger(0) );
-        }
+		    RETURN ( __mkSmallInteger(0) );
+		}
+
+		if (matchP[2] == 0) {
+		    /* two character matches */
+		    unsigned char m1 = matchP[0];
+		    unsigned char m2 = matchP[1];
+
+		    while (c = *cp++) {
+			if ((c == m1) || (c == m2)) {
+			    RETURN ( __mkSmallInteger(index) );
+			}
+			index++;
+		    }
+		    RETURN ( __mkSmallInteger(0) );
+		}
+
+		min = max = matchP[0];
+
+		for (ccp = matchP+1; *ccp ; ccp++) {
+		    unsigned char c = *ccp;
+		    if (c < min) min = c;
+		    else if (c > max) max = c;
+		}
+
+		while (c = *cp++) {
+		    if ((c >= min) && (c <= max)) {
+			for (ccp = matchP; *ccp ; ccp++) {
+			    if (*ccp == c) {
+				RETURN ( __mkSmallInteger(index) );
+			    }
+			}
+		    }
+		    index++;
+		}
+	    }
+	    RETURN ( __mkSmallInteger(0) );
+	}
     }
 %}.
     "/
@@ -1251,43 +1202,43 @@
     OBJ cls;
 
     if (__isCharacter(aCharacter)) {
-        limit = __stringSize(self);
-        count = 0;
-        byteValue = __intVal(_characterVal(aCharacter));
-        if (byteValue <= 0xFF) {
-            cp = __stringVal(self);
-            if ((cls = __qClass(self)) != String) {
-                int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-                limit -= n;
-                cp += n;
-            }
-            /* loop unrolled and software-pipelined 
-             * (gives 30-40% speedup on Intel-DUO using borland bcc55)
-             */
-            while (limit >= 4) {
-                register unsigned char c1, c2;
-
-                c1 = cp[0];
-                limit -= 4;
-                c2 = cp[1];
-                if (c1 == byteValue) count++;
-                c1 = cp[2];
-                if (c2 == byteValue) count++;
-                c2 = cp[3];
-                if (c1 == byteValue) count++;
-                cp += 4;
-                if (c2 == byteValue) count++;
-            }
-            while (limit > 0) {
-                register unsigned char c1;
-
-                c1 = cp[0];
-                limit--;
-                if (c1 == byteValue) count++;
-                cp ++;
-            }
-        }
-        RETURN ( __mkSmallInteger(count) );
+	limit = __stringSize(self);
+	count = 0;
+	byteValue = __intVal(_characterVal(aCharacter));
+	if (byteValue <= 0xFF) {
+	    cp = __stringVal(self);
+	    if ((cls = __qClass(self)) != String) {
+		int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+		limit -= n;
+		cp += n;
+	    }
+	    /* loop unrolled and software-pipelined
+	     * (gives 30-40% speedup on Intel-DUO using borland bcc55)
+	     */
+	    while (limit >= 4) {
+		register unsigned char c1, c2;
+
+		c1 = cp[0];
+		limit -= 4;
+		c2 = cp[1];
+		if (c1 == byteValue) count++;
+		c1 = cp[2];
+		if (c2 == byteValue) count++;
+		c2 = cp[3];
+		if (c1 == byteValue) count++;
+		cp += 4;
+		if (c2 == byteValue) count++;
+	    }
+	    while (limit > 0) {
+		register unsigned char c1;
+
+		c1 = cp[0];
+		limit--;
+		if (c1 == byteValue) count++;
+		cp ++;
+	    }
+	}
+	RETURN ( __mkSmallInteger(count) );
     }
 %}.
     ^ super occurrencesOf:aCharacter
@@ -1299,7 +1250,7 @@
      'hello world' occurrencesOf:$x
      'hello world' occurrencesOf:1
      Time millisecondsToRun:[
-        1000000 timesRepeat:[ 'abcdefghijklmn' occurrencesOf:$x ]
+	1000000 timesRepeat:[ 'abcdefghijklmn' occurrencesOf:$x ]
      ]. 219 203 156 203 204 204 219 172 187 187 141
     "
 ! !
@@ -1583,45 +1534,45 @@
     OBJ myCls;
 
     if (__isNonNilObject(s)) {
-        cls = __qClass(s);
-        myCls = __qClass(self);
-
-        if (__isStringLike(s) || (cls == myCls)) {
-            cp1 = __stringVal(self);
-
-            /*
-             * care for instances of subclasses ...
-             */
-            if (myCls != String) {
-                int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(myCls)->c_ninstvars));
-
-                cp1 += n;
-            }
-
-            cp2 = __stringVal(s);
-            /*
-             * care for instances of subclasses ...
-             */
-            if (cls != String) {
-                int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-
-                cp2 += n;
-            }
+	cls = __qClass(s);
+	myCls = __qClass(self);
+
+	if (__isStringLike(s) || (cls == myCls)) {
+	    cp1 = __stringVal(self);
+
+	    /*
+	     * care for instances of subclasses ...
+	     */
+	    if (myCls != String) {
+		int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(myCls)->c_ninstvars));
+
+		cp1 += n;
+	    }
+
+	    cp2 = __stringVal(s);
+	    /*
+	     * care for instances of subclasses ...
+	     */
+	    if (cls != String) {
+		int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+
+		cp2 += n;
+	    }
 
 #ifdef HAS_STRCOLL
-            cmp = strcoll(cp1, cp2);
+	    cmp = strcoll(cp1, cp2);
 #else
-            cmp = strcmp(cp1, cp2);
+	    cmp = strcmp(cp1, cp2);
 #endif
 
-            if (cmp > 0) {
-                RETURN ( __mkSmallInteger(1) );
-            }
-            if (cmp < 0) {
-                RETURN ( __mkSmallInteger(-1) );
-            }
-            RETURN ( __mkSmallInteger(0) );
-        }
+	    if (cmp > 0) {
+		RETURN ( __mkSmallInteger(1) );
+	    }
+	    if (cmp < 0) {
+		RETURN ( __mkSmallInteger(-1) );
+	    }
+	    RETURN ( __mkSmallInteger(0) );
+	}
     }
 %}.
     "
@@ -1643,10 +1594,10 @@
     cp = __stringVal(self);
     l = __stringSize(self);
     if (__qClass(self) != @global(String)) {
-        int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-
-        cp += n;
-        l -= n;
+	int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+
+	cp += n;
+	l -= n;
     }
 
     /*
@@ -1656,30 +1607,30 @@
     val = 0;
     switch (l) {
     default:
-        for (cp0 = cp, cp += l - 1; cp >= cp0; cp--) {
-            val = (val << 4) + *cp;
-            if (g = (val & 0xF0000000)) {
-                val ^= g >> 24;
-                val ^= g;
-            }
-        }
-        break;
+	for (cp0 = cp, cp += l - 1; cp >= cp0; cp--) {
+	    val = (val << 4) + *cp;
+	    if (g = (val & 0xF0000000)) {
+		val ^= g >> 24;
+		val ^= g;
+	    }
+	}
+	break;
     case 7:
-        val = cp[6] << 4;
+	val = cp[6] << 4;
     case 6:
-        val = (val + cp[5]) << 4;
+	val = (val + cp[5]) << 4;
     case 5:
-        val = (val + cp[4]) << 4;
+	val = (val + cp[4]) << 4;
     case 4:
-        val = (val + cp[3]) << 4;
+	val = (val + cp[3]) << 4;
     case 3:
-        val = (val + cp[2]) << 4;
+	val = (val + cp[2]) << 4;
     case 2:
-        val = (val + cp[1]) << 4;
+	val = (val + cp[1]) << 4;
     case 1:
-        val = val + cp[0];
+	val = val + cp[0];
     case 0:
-        break;
+	break;
     }
 
     /*
@@ -1703,10 +1654,10 @@
     cp = __stringVal(self);
     l = __stringSize(self);
     if (__qClass(self) != @global(String)) {
-        int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-
-        cp += n;
-        l -= n;
+	int n = __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+
+	cp += n;
+	l -= n;
     }
 
     /*
@@ -1714,31 +1665,31 @@
      */
     val = 0;
     while (l >= 4) {
-        l -= 4;
-        ch = cp[0];
-        val = (val * 65599) + ch;
-        ch = cp[1];
-        val = (val * 65599) + ch;
-        ch = cp[2];
-        val = (val * 65599) + ch;
-        ch = cp[3];
-        val = (val * 65599) + ch;
-        cp += 4;
+	l -= 4;
+	ch = cp[0];
+	val = (val * 65599) + ch;
+	ch = cp[1];
+	val = (val * 65599) + ch;
+	ch = cp[2];
+	val = (val * 65599) + ch;
+	ch = cp[3];
+	val = (val * 65599) + ch;
+	cp += 4;
     }
     while (l) {
-        l--;
-        ch = *cp++;
-        val = (val * 65599) + ch;
+	l--;
+	ch = *cp++;
+	val = (val * 65599) + ch;
     }
     RETURN ( __mkSmallInteger(val & _MAX_INT));
 %}
 
     "
      'a' hash_sdbm
-     'ab' hash_sdbm 
+     'ab' hash_sdbm
      'ab' asUnicode16String hash_sdbm
     "
-    
+
     "Created: / 26-12-2011 / 13:53:09 / cg"
 !
 
@@ -1850,21 +1801,21 @@
     "Answer an array with all the substrings of the receiver separated by
      separator characters (space, cr, tab, linefeed, formfeed, etc).
      CG: This is ported Squeak code, and I am not sure if it is more efficient than
-         the inherited one... after all: who added it anyway ?"
+	 the inherited one... after all: who added it anyway ?"
 
     | substrings start end |
 
     substrings := OrderedCollection new.
     start := 1.
     [start <= self size] whileTrue: [
-        (self at: start) isSeparator ifFalse: [
-            end := start + 1.
-            [end <= self size and: [(self at: end) isSeparator not]]
-                whileTrue: [end := end + 1].
-            substrings add: (self copyFrom: start to: end - 1).
-            start := end - 1
-        ].
-        start := start + 1
+	(self at: start) isSeparator ifFalse: [
+	    end := start + 1.
+	    [end <= self size and: [(self at: end) isSeparator not]]
+		whileTrue: [end := end + 1].
+	    substrings add: (self copyFrom: start to: end - 1).
+	    start := end - 1
+	].
+	start := start + 1
     ].
     ^ substrings asArray
 !
@@ -1876,10 +1827,10 @@
      Notice, that all singleByte strings are already 0-terminated in ST/X, whereas wide
      strings are not."
 
-    ^ self 
+    ^ self
 
     "
-     'abc' asAsciiZ               
+     'abc' asAsciiZ
      'abc' asWideString asAsciiZ
     "
 !
@@ -1934,8 +1885,8 @@
 
     |bytes sz|
 
-    sz := self byteSize.
-    bytes := ExternalBytes basicNew allocateBytes:sz.
+    sz := self size.
+    bytes := ExternalBytes basicNew allocateBytes:sz + 1.
     bytes replaceFrom:1 to:sz with:self startingAt:1.
     bytes at:(sz + 1) put:0.
     ^ bytes
@@ -1946,7 +1897,7 @@
      ObjectMemory garbageCollect
     "
 
-    "Created: / 05-06-2012 / 14:16:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 05-06-2012 / 14:12:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 asImmutableString
@@ -1956,15 +1907,15 @@
 !
 
 asPackageId
-    "given a package-string as receiver, return a packageId object. 
+    "given a package-string as receiver, return a packageId object.
      packageIds hide the details of module/directory handling inside the path"
 
     ^ PackageId from: self asSymbol
 
     "
-     'stx:libbasic' asPackageId  
-     'stx:goodies/net/ssl' asPackageId  
-     'stx:hello' asPackageId  
+     'stx:libbasic' asPackageId
+     'stx:goodies/net/ssl' asPackageId
+     'stx:hello' asPackageId
     "
 
     "Created: / 18-08-2006 / 12:19:54 / cg"
@@ -2181,77 +2132,77 @@
     OBJ myClass, argClass, newString;
 
     if (__isNonNilObject(s)) {
-        myClass = __qClass(self);
-        argClass = __qClass(s);
-        /*
-         * can do it here if both are Strings/Symbols:
-         */
-        if (((myClass == _string) || (myClass == Symbol))
-         && ((argClass == _string) || (argClass == Symbol))) {
-            l1 = __stringSize(self);
-            l2 = __stringSize(s);
-
-            sz = OHDR_SIZE + l1 + l2 + 1;
-            __qNew(newString, sz);      /* OBJECT ALLOCATION */
-            if (newString != nil) {
-                char *cp1, *cp2;
-                REGISTER unsigned char *dstp;
-
-                __InstPtr(newString)->o_class = String;
-                __qSTORE(newString, String);
-                dstp = __stringVal(newString);
-                cp1 = (char *) __stringVal(self);
-                cp2 = (char *) __stringVal(aString);
+	myClass = __qClass(self);
+	argClass = __qClass(s);
+	/*
+	 * can do it here if both are Strings/Symbols:
+	 */
+	if (((myClass == _string) || (myClass == Symbol))
+	 && ((argClass == _string) || (argClass == Symbol))) {
+	    l1 = __stringSize(self);
+	    l2 = __stringSize(s);
+
+	    sz = OHDR_SIZE + l1 + l2 + 1;
+	    __qNew(newString, sz);      /* OBJECT ALLOCATION */
+	    if (newString != nil) {
+		char *cp1, *cp2;
+		REGISTER unsigned char *dstp;
+
+		__InstPtr(newString)->o_class = String;
+		__qSTORE(newString, String);
+		dstp = __stringVal(newString);
+		cp1 = (char *) __stringVal(self);
+		cp2 = (char *) __stringVal(aString);
 
 #ifdef bcopy4
-                /* knowing that allocation is 4-byte aligned and
-                 * size rounded up to next 4-byte, the first copy
-                 * can be done word-wise.
-                 * that speeds up size-10-string , size-10-string
-                 * by 10% on a P5/200.
-                 */
-                {
-                    int nw = l1 >> 2;
-
-                    if (l1 & 3) nw++;
-                    bcopy4(cp1, dstp, nw);
-                    dstp += l1;
-                }
+		/* knowing that allocation is 4-byte aligned and
+		 * size rounded up to next 4-byte, the first copy
+		 * can be done word-wise.
+		 * that speeds up size-10-string , size-10-string
+		 * by 10% on a P5/200.
+		 */
+		{
+		    int nw = l1 >> 2;
+
+		    if (l1 & 3) nw++;
+		    bcopy4(cp1, dstp, nw);
+		    dstp += l1;
+		}
 #else
 # ifdef FAST_MEMCPY
-                memcpy(dstp, cp1, l1);
-                dstp += l1;
+		memcpy(dstp, cp1, l1);
+		dstp += l1;
 # else
-                while (l1 >= 4) {
-                    *(int *)dstp = *(int *)cp1;
-                    dstp += 4; cp1 += 4;
-                    l1 -= 4;
-                }
-                while (l1--) *dstp++ = *cp1++;
+		while (l1 >= 4) {
+		    *(int *)dstp = *(int *)cp1;
+		    dstp += 4; cp1 += 4;
+		    l1 -= 4;
+		}
+		while (l1--) *dstp++ = *cp1++;
 # endif
 #endif
 
 #ifdef bcopy4
-                if (((INT)dstp & 3) == 0) {
-                    int nw = l2 >> 2;
-
-                    if (l2 & 3) nw++;
-                    bcopy4(cp2, dstp, nw);
-                    *(dstp + l2) = '\0';
-                    RETURN ( newString );
-                }
+		if (((INT)dstp & 3) == 0) {
+		    int nw = l2 >> 2;
+
+		    if (l2 & 3) nw++;
+		    bcopy4(cp2, dstp, nw);
+		    *(dstp + l2) = '\0';
+		    RETURN ( newString );
+		}
 #endif
 
 #ifdef FAST_MEMCPY
-                memcpy(dstp, cp2, l2+1);
-                dstp[l2] = '\0';
+		memcpy(dstp, cp2, l2+1);
+		dstp[l2] = '\0';
 #else
-                while (l2--) *dstp++ = *cp2++;
-                *dstp = '\0';
+		while (l2--) *dstp++ = *cp2++;
+		*dstp = '\0';
 #endif
-                RETURN ( newString );
-            }
-        }
+		RETURN ( newString );
+	    }
+	}
     }
 %}.
     ^ super , aString
@@ -2278,34 +2229,34 @@
 #endif
     REGISTER unsigned char *dstp;
 
-    if (__isStringLike(self) 
-            && __isStringLike(string1)
-            && __isStringLike(string2)) {
-        len1 = __stringSize(self);
-        len2 = __stringSize(string1);
-        len3 = __stringSize(string2);
-        sz = OHDR_SIZE + len1 + len2 + len3 + 1;
-        __qNew(newString, sz);  /* OBJECT ALLOCATION */
-        if (newString != nil) {
-            __InstPtr(newString)->o_class = String;
-            __qSTORE(newString, String);
-            dstp = __stringVal(newString);
+    if (__isStringLike(self)
+	    && __isStringLike(string1)
+	    && __isStringLike(string2)) {
+	len1 = __stringSize(self);
+	len2 = __stringSize(string1);
+	len3 = __stringSize(string2);
+	sz = OHDR_SIZE + len1 + len2 + len3 + 1;
+	__qNew(newString, sz);  /* OBJECT ALLOCATION */
+	if (newString != nil) {
+	    __InstPtr(newString)->o_class = String;
+	    __qSTORE(newString, String);
+	    dstp = __stringVal(newString);
 #ifdef FAST_MEMCPY
-            memcpy(dstp, __stringVal(self), len1);
-            memcpy(dstp + len1, __stringVal(string1), len2);
-            memcpy(dstp + len1 + len2, __stringVal(string2), len3+1);
-            *(dstp + len1 + len2 + len3) = '\0';
+	    memcpy(dstp, __stringVal(self), len1);
+	    memcpy(dstp + len1, __stringVal(string1), len2);
+	    memcpy(dstp + len1 + len2, __stringVal(string2), len3+1);
+	    *(dstp + len1 + len2 + len3) = '\0';
 #else
-            srcp = __stringVal(self);
-            while (len1--) *dstp++ = *srcp++;
-            srcp = __stringVal(string1);
-            while (len2--) *dstp++ = *srcp++;
-            srcp = __stringVal(string2);
-            while (len3--) *dstp++ = *srcp++;
-            *dstp = '\0';
+	    srcp = __stringVal(self);
+	    while (len1--) *dstp++ = *srcp++;
+	    srcp = __stringVal(string1);
+	    while (len2--) *dstp++ = *srcp++;
+	    srcp = __stringVal(string2);
+	    while (len3--) *dstp++ = *srcp++;
+	    *dstp = '\0';
 #endif
-            RETURN ( newString );
-        }
+	    RETURN ( newString );
+	}
     }
 %}.
     ^ super , string1 , string2
@@ -2325,39 +2276,39 @@
 #endif
     REGISTER unsigned char *dstp;
 
-    if (__isStringLike(self) 
+    if (__isStringLike(self)
      && __isStringLike(string1)
      && __isStringLike(string2)
      && __isStringLike(string3)) {
-        len1 = __stringSize(self);
-        len2 = __stringSize(string1);
-        len3 = __stringSize(string2);
-        len4 = __stringSize(string3);
-        sz = OHDR_SIZE + len1 + len2 + len3 + len4 + 1;
-        __qNew(newString, sz);  /* OBJECT ALLOCATION */
-        if (newString != nil) {
-            __InstPtr(newString)->o_class = String;
-            __qSTORE(newString, String);
-            dstp = __stringVal(newString);
+	len1 = __stringSize(self);
+	len2 = __stringSize(string1);
+	len3 = __stringSize(string2);
+	len4 = __stringSize(string3);
+	sz = OHDR_SIZE + len1 + len2 + len3 + len4 + 1;
+	__qNew(newString, sz);  /* OBJECT ALLOCATION */
+	if (newString != nil) {
+	    __InstPtr(newString)->o_class = String;
+	    __qSTORE(newString, String);
+	    dstp = __stringVal(newString);
 #ifdef FAST_MEMCPY
-            memcpy(dstp, __stringVal(self), len1);
-            memcpy(dstp + len1, __stringVal(string1), len2);
-            memcpy(dstp + len1 + len2, __stringVal(string2), len3);
-            memcpy(dstp + len1 + len2 + len3, __stringVal(string3), len4+1);
-            *(dstp + len1 + len2 + len3 + len4) = '\0';
+	    memcpy(dstp, __stringVal(self), len1);
+	    memcpy(dstp + len1, __stringVal(string1), len2);
+	    memcpy(dstp + len1 + len2, __stringVal(string2), len3);
+	    memcpy(dstp + len1 + len2 + len3, __stringVal(string3), len4+1);
+	    *(dstp + len1 + len2 + len3 + len4) = '\0';
 #else
-            srcp = __stringVal(self);
-            while (len1--) *dstp++ = *srcp++;
-            srcp = __stringVal(string1);
-            while (len2--) *dstp++ = *srcp++;
-            srcp = __stringVal(string2);
-            while (len3--) *dstp++ = *srcp++;
-            srcp = __stringVal(string3);
-            while (len4--) *dstp++ = *srcp++;
-            *dstp = '\0';
+	    srcp = __stringVal(self);
+	    while (len1--) *dstp++ = *srcp++;
+	    srcp = __stringVal(string1);
+	    while (len2--) *dstp++ = *srcp++;
+	    srcp = __stringVal(string2);
+	    while (len3--) *dstp++ = *srcp++;
+	    srcp = __stringVal(string3);
+	    while (len4--) *dstp++ = *srcp++;
+	    *dstp = '\0';
 #endif
-            RETURN ( newString );
-        }
+	    RETURN ( newString );
+	}
     }
 %}.
     ^ super , string1 , string2 , string3
@@ -2612,7 +2563,7 @@
      of its named instvars ...
     "
     (self isMemberOf:String) ifTrue:[
-        ^ self copyFrom:1
+	^ self copyFrom:1
     ].
     ^ super deepCopyUsing:aDictionary postCopySelector:postCopySelector
 !
@@ -2800,74 +2751,74 @@
     if (__isStringLike(aString)
      && __isString(self)
      && __bothSmallInteger(start, stop)) {
-        len = __stringSize(self);
-        index1 = __intVal(start);
-        index2 = __intVal(stop);
-        count = index2 - index1 + 1;
-        if (count <= 0) {
-             RETURN (self);
-        }
-        if ((index2 <= len) && (index1 > 0)) {
-            repLen = __stringSize(aString);
-            repIndex = __intVal(repStart);
-            if ((repIndex > 0) && ((repIndex + count - 1) <= repLen)) {
-                srcp = __stringVal(aString) + repIndex - 1;
-                dstp = __stringVal(self) + index1 - 1;
-                if (aString == self) {
-                    /* take care of overlapping copy */
-                    if (srcp < dstp) {
-                        /* must do a reverse copy */
-                        srcp += count;
-                        dstp += count;
-                        while (count-- > 0) {
-                            *--dstp = *--srcp;
-                        }
-                        RETURN (self);
-                    }
-                }
+	len = __stringSize(self);
+	index1 = __intVal(start);
+	index2 = __intVal(stop);
+	count = index2 - index1 + 1;
+	if (count <= 0) {
+	     RETURN (self);
+	}
+	if ((index2 <= len) && (index1 > 0)) {
+	    repLen = __stringSize(aString);
+	    repIndex = __intVal(repStart);
+	    if ((repIndex > 0) && ((repIndex + count - 1) <= repLen)) {
+		srcp = __stringVal(aString) + repIndex - 1;
+		dstp = __stringVal(self) + index1 - 1;
+		if (aString == self) {
+		    /* take care of overlapping copy */
+		    if (srcp < dstp) {
+			/* must do a reverse copy */
+			srcp += count;
+			dstp += count;
+			while (count-- > 0) {
+			    *--dstp = *--srcp;
+			}
+			RETURN (self);
+		    }
+		}
 #ifdef bcopy4
-                /* copy quadbytes if pointers are aligned */
-                /*
-                 * no sizeof(int) here please -
-                 * - bcopy4 (if defined) copies 4-bytes on ALL machines
-                 */
-                if ((count > 12)
-                 && (((unsigned INT)srcp & 3) == 0)
-                 && (((unsigned INT)dstp & 3) == 0)) {
-                    int n;
-
-                    n = count >> 2;        /* make it quads */
-                    bcopy4(srcp, dstp, n);
-                    n <<= 2;               /* back to chars */
-                    dstp += n;
-                    srcp += n;
-                    count -= n;
-                }
-                while (count-- > 0) {
-                    *dstp++ = *srcp++;
-                }
+		/* copy quadbytes if pointers are aligned */
+		/*
+		 * no sizeof(int) here please -
+		 * - bcopy4 (if defined) copies 4-bytes on ALL machines
+		 */
+		if ((count > 12)
+		 && (((unsigned INT)srcp & 3) == 0)
+		 && (((unsigned INT)dstp & 3) == 0)) {
+		    int n;
+
+		    n = count >> 2;        /* make it quads */
+		    bcopy4(srcp, dstp, n);
+		    n <<= 2;               /* back to chars */
+		    dstp += n;
+		    srcp += n;
+		    count -= n;
+		}
+		while (count-- > 0) {
+		    *dstp++ = *srcp++;
+		}
 #else
 # ifdef FAST_MEMCPY
-                bcopy(srcp, dstp, count);
+		bcopy(srcp, dstp, count);
 # else
-                /* copy longs if pointers are aligned */
-                if ((((unsigned INT)srcp & (sizeof(INT)-1)) == 0)
-                 && (((unsigned INT)dstp & (sizeof(INT)-1)) == 0)) {
-                    while (count >= sizeof(INT)) {
-                        *((unsigned INT *)dstp) = *((unsigned INT *)srcp);
-                        dstp += sizeof(INT);
-                        srcp += sizeof(INT);
-                        count -= sizeof(INT);
-                    }
-                }
-                while (count-- > 0) {
-                    *dstp++ = *srcp++;
-                }
+		/* copy longs if pointers are aligned */
+		if ((((unsigned INT)srcp & (sizeof(INT)-1)) == 0)
+		 && (((unsigned INT)dstp & (sizeof(INT)-1)) == 0)) {
+		    while (count >= sizeof(INT)) {
+			*((unsigned INT *)dstp) = *((unsigned INT *)srcp);
+			dstp += sizeof(INT);
+			srcp += sizeof(INT);
+			count -= sizeof(INT);
+		    }
+		}
+		while (count-- > 0) {
+		    *dstp++ = *srcp++;
+		}
 # endif
 #endif
-                RETURN (self);
-            }
-        }
+		RETURN (self);
+	    }
+	}
     }
 #endif
 %}.
@@ -3091,44 +3042,44 @@
     extern void *malloc();
 
     if (__isStringLike(formatString)) {
-        cp = (char *)__stringVal(self);
-        if (__qClass(self) != String) {
-            cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
-        }
+	cp = (char *)__stringVal(self);
+	if (__qClass(self) != String) {
+	    cp += __OBJS2BYTES__(__intVal(__ClassInstPtr(__qClass(self))->c_ninstvars));
+	}
 again:
-        /*
-         * actually only needed on sparc: since thisContext is
-         * in a global register, which gets destroyed by printf,
-         * manually save it here - very stupid ...
-         */
-        __BEGIN_PROTECT_REGISTERS__
-
-        len = snprintf(buf, bufsize, (char *)__stringVal(formatString), cp);
-
-        __END_PROTECT_REGISTERS__
-
-        if ((len < 0) || (len > bufsize)) {
-            if (len < 0) {
-                bufsize = bufsize * 2;
-            } else {
-                bufsize = len + 1;
-            }
-            if (mallocbuf)
-                free(mallocbuf);
-            buf = mallocbuf = malloc(bufsize);
-            if (buf == NULL)
-                goto fail;
-            goto again;
-        }
-
-        s = __MKSTRING_L(buf, len);
-
-        if (mallocbuf)
-            free(mallocbuf);
-
-        if (s != nil) {
-            RETURN (s);
-        }
+	/*
+	 * actually only needed on sparc: since thisContext is
+	 * in a global register, which gets destroyed by printf,
+	 * manually save it here - very stupid ...
+	 */
+	__BEGIN_PROTECT_REGISTERS__
+
+	len = snprintf(buf, bufsize, (char *)__stringVal(formatString), cp);
+
+	__END_PROTECT_REGISTERS__
+
+	if ((len < 0) || (len > bufsize)) {
+	    if (len < 0) {
+		bufsize = bufsize * 2;
+	    } else {
+		bufsize = len + 1;
+	    }
+	    if (mallocbuf)
+		free(mallocbuf);
+	    buf = mallocbuf = malloc(bufsize);
+	    if (buf == NULL)
+		goto fail;
+	    goto again;
+	}
+
+	s = __MKSTRING_L(buf, len);
+
+	if (mallocbuf)
+	    free(mallocbuf);
+
+	if (s != nil) {
+	    RETURN (s);
+	}
     }
 fail:;
 %}.
@@ -3316,7 +3267,7 @@
 reverse
     "in-place reverse the characters of the string.
      WARNING: this is a destructive operation, which modifies the receiver.
-              Please use reversed (with a d) for a functional version."
+	      Please use reversed (with a d) for a functional version."
 
     "Q: is there a need to redefine it here ?"
 
@@ -3326,16 +3277,16 @@
     REGISTER unsigned char *hip, *lowp;
 
     if (__isString(self)) {
-        lowp = __stringVal(self);
-        hip = lowp + __stringSize(self) - 1;
-        while (lowp < hip) {
-            c = *lowp;
-            *lowp = *hip;
-            *hip = c;
-            lowp++;
-            hip--;
-        }
-        RETURN ( self );
+	lowp = __stringVal(self);
+	hip = lowp + __stringSize(self) - 1;
+	while (lowp < hip) {
+	    c = *lowp;
+	    *lowp = *hip;
+	    *hip = c;
+	    lowp++;
+	    hip--;
+	}
+	RETURN ( self );
     }
 %}.
     ^ super reverse
@@ -3350,100 +3301,100 @@
     |notFound|
 
 %{
-    if (__isStringLike(self) 
+    if (__isStringLike(self)
      && __isStringLike(aSubString)
      && (caseSensitive == true)
      && (__isSmallInteger(startIndex))
      && (__intVal(startIndex) > 0)
     ) {
-        unsigned char *y = __stringVal(self);
-        unsigned char *x = __stringVal(aSubString);
-        int m = __stringSize(aSubString);
-        int n = __stringSize(self);
+	unsigned char *y = __stringVal(self);
+	unsigned char *x = __stringVal(aSubString);
+	int m = __stringSize(aSubString);
+	int n = __stringSize(self);
 #       define XSIZE 256
 #       define ASIZE 256
 #       define MAX(a,b) (a>b ? a : b)
 
-        if (m == 0) {
+	if (m == 0) {
 #if 1
-            /* empty string does not match */
-            RETURN(__mkSmallInteger(0));
+	    /* empty string does not match */
+	    RETURN(__mkSmallInteger(0));
 #else
-            /* empty string matches */
-            RETURN(startIndex);
+	    /* empty string matches */
+	    RETURN(startIndex);
 #endif
-        }
-        if (m <= XSIZE) {
-            int i, j, bmGs[XSIZE+1], bmBc[ASIZE];
+	}
+	if (m <= XSIZE) {
+	    int i, j, bmGs[XSIZE+1], bmBc[ASIZE];
 
 #           define preBmBc(x, m, bmBc) {          \
-               int i;                             \
-                                                  \
-               for (i = 0; i < ASIZE; ++i)        \
-                  bmBc[i] = m;                    \
-               for (i = 0; i < m - 1; ++i)        \
-                  bmBc[x[i]] = m - i - 1;         \
-            }
+	       int i;                             \
+						  \
+	       for (i = 0; i < ASIZE; ++i)        \
+		  bmBc[i] = m;                    \
+	       for (i = 0; i < m - 1; ++i)        \
+		  bmBc[x[i]] = m - i - 1;         \
+	    }
 
 #           define suffixes(x, m, suff) {                       \
-               int f, g, i;                                     \
-                                                                \
-               suff[m - 1] = m;                                 \
-               g = m - 1;                                       \
-               for (i = m - 2; i >= 0; --i) {                   \
-                  if (i > g && suff[i + m - 1 - f] < i - g)     \
-                     suff[i] = suff[i + m - 1 - f];             \
-                  else {                                        \
-                     if (i < g)                                 \
-                        g = i;                                  \
-                     f = i;                                     \
-                     while (g >= 0 && x[g] == x[g + m - 1 - f]) \
-                        --g;                                    \
-                     suff[i] = f - g;                           \
-                  }                                             \
-               }                                                \
-            }
+	       int f, g, i;                                     \
+								\
+	       suff[m - 1] = m;                                 \
+	       g = m - 1;                                       \
+	       for (i = m - 2; i >= 0; --i) {                   \
+		  if (i > g && suff[i + m - 1 - f] < i - g)     \
+		     suff[i] = suff[i + m - 1 - f];             \
+		  else {                                        \
+		     if (i < g)                                 \
+			g = i;                                  \
+		     f = i;                                     \
+		     while (g >= 0 && x[g] == x[g + m - 1 - f]) \
+			--g;                                    \
+		     suff[i] = f - g;                           \
+		  }                                             \
+	       }                                                \
+	    }
 
 #           define preBmGs(x, m, bmGs) {                        \
-               int i, j, suff[XSIZE];                           \
-                                                                \
-               suffixes(x, m, suff);                            \
-                                                                \
-               for (i = 0; i < m; ++i)                          \
-                  bmGs[i] = m;                                  \
-               j = 0;                                           \
-               for (i = m - 1; i >= 0; --i)                     \
-                  if (suff[i] == i + 1)                         \
-                     for (; j < m - 1 - i; ++j)                 \
-                        if (bmGs[j] == m)                       \
-                           bmGs[j] = m - 1 - i;                 \
-               for (i = 0; i <= m - 2; ++i)                     \
-                  bmGs[m - 1 - suff[i]] = m - 1 - i;            \
-            }
-
-            /* Preprocessing */
-            preBmGs(x, m, bmGs);
-            preBmBc(x, m, bmBc);
-
-            /* Searching */
-            j = __intVal(startIndex) - 1;
-            while (j <= n - m) {
-               for (i = m - 1; i >= 0 && x[i] == y[i + j]; --i);
-               if (i < 0) {
-                  RETURN (__mkSmallInteger(j+1));
-                  j += bmGs[0];  
-               } else {
-                  int s1 = bmGs[i];
-                  int s2 = bmBc[y[i + j]] - m + 1 + i;
-                  j += MAX(s1, s2);
-               }
-            }
-            notFound = true;
-        }
+	       int i, j, suff[XSIZE];                           \
+								\
+	       suffixes(x, m, suff);                            \
+								\
+	       for (i = 0; i < m; ++i)                          \
+		  bmGs[i] = m;                                  \
+	       j = 0;                                           \
+	       for (i = m - 1; i >= 0; --i)                     \
+		  if (suff[i] == i + 1)                         \
+		     for (; j < m - 1 - i; ++j)                 \
+			if (bmGs[j] == m)                       \
+			   bmGs[j] = m - 1 - i;                 \
+	       for (i = 0; i <= m - 2; ++i)                     \
+		  bmGs[m - 1 - suff[i]] = m - 1 - i;            \
+	    }
+
+	    /* Preprocessing */
+	    preBmGs(x, m, bmGs);
+	    preBmBc(x, m, bmBc);
+
+	    /* Searching */
+	    j = __intVal(startIndex) - 1;
+	    while (j <= n - m) {
+	       for (i = m - 1; i >= 0 && x[i] == y[i + j]; --i);
+	       if (i < 0) {
+		  RETURN (__mkSmallInteger(j+1));
+		  j += bmGs[0];
+	       } else {
+		  int s1 = bmGs[i];
+		  int s2 = bmBc[y[i + j]] - m + 1 + i;
+		  j += MAX(s1, s2);
+	       }
+	    }
+	    notFound = true;
+	}
     }
 %}.
     notFound == true ifTrue:[
-        ^ exceptionValue value.
+	^ exceptionValue value.
     ].
     ^ super indexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:caseSensitive
 ! !
@@ -3461,32 +3412,32 @@
     REGISTER OBJ slf = self;
 
     if (__isStringLike(slf) && __isStringLike(aStringOrChar)) {
-        len1 = __qSize(slf);
-        len2 = __qSize(aStringOrChar);
-        if (len1 < len2) {
-            RETURN ( false );
-        }
-
-        src1 = __stringVal(slf) + (len1 - len2);
-        src2 = __stringVal(aStringOrChar);
-        while (c = *src2++) {
-            if (c != *src1++) {
-                RETURN ( false );
-            }
-        }
-        RETURN (true);
+	len1 = __qSize(slf);
+	len2 = __qSize(aStringOrChar);
+	if (len1 < len2) {
+	    RETURN ( false );
+	}
+
+	src1 = __stringVal(slf) + (len1 - len2);
+	src2 = __stringVal(aStringOrChar);
+	while (c = *src2++) {
+	    if (c != *src1++) {
+		RETURN ( false );
+	    }
+	}
+	RETURN (true);
     }
     if (__isCharacter(aStringOrChar)) {
-        int val;
-
-        val = __intVal(_characterVal(aStringOrChar));
-        if ((unsigned)val <= 0xFF) {
-            len1 = __stringSize(slf);
-            if (len1 > 0) {
-                RETURN ( (__stringVal(slf)[len1-1] == val) ? true : false);
-            }
-        }
-        RETURN ( false );
+	int val;
+
+	val = __intVal(_characterVal(aStringOrChar));
+	if ((unsigned)val <= 0xFF) {
+	    len1 = __stringSize(slf);
+	    if (len1 > 0) {
+		RETURN ( (__stringVal(slf)[len1-1] == val) ? true : false);
+	    }
+	}
+	RETURN ( false );
     }
 %}.
     ^ super endsWith:aStringOrChar
@@ -3805,13 +3756,14 @@
 !String class methodsFor:'documentation'!
 
 version
-    ^ '$Id: String.st 10812 2012-06-05 12:18:28Z vranyj1 $'
+    ^ '$Id: String.st 10814 2012-06-05 13:35:12Z vranyj1 $'
+
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/String.st,v 1.281 2012/04/01 11:27:41 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/String.st,v 1.282 2012/06/05 12:16:22 vrany Exp §'
 !
 
 version_SVN
-    ^ '$Id: String.st 10812 2012-06-05 12:18:28Z vranyj1 $'
+    ^ '$Id: String.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
--- a/UninterpretedBytes.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/UninterpretedBytes.st	Tue Jun 05 14:35:12 2012 +0100
@@ -397,8 +397,8 @@
     ^ (self byteAt:index) decodeFromBCD
 
     "
-     #[ 16r55 ] bcdByteAt:1  
-     #[ 16r99] bcdByteAt:1   
+     #[ 16r55 ] bcdByteAt:1
+     #[ 16r99] bcdByteAt:1
      #[ 16rAA] bcdByteAt:1
     "
 
@@ -411,7 +411,7 @@
      (i.e. the value n is encoded as: ((n // 10) * 16) + (n \\ 10)"
 
     (aNumber between:0 and:99) ifFalse:[
-        self error:'invalid value for BCD encoding'
+	self error:'invalid value for BCD encoding'
     ].
     ^ self byteAt:index put:aNumber encodeAsBCD
 
@@ -453,9 +453,9 @@
     |b "{ Class: SmallInteger }"|
 
     aSignedByteValue >= 0 ifTrue:[
-        b := aSignedByteValue
+	b := aSignedByteValue
     ] ifFalse:[
-        b := 16r100 + aSignedByteValue
+	b := 16r100 + aSignedByteValue
     ].
     self at:index put:b.
     ^ aSignedByteValue
@@ -2448,7 +2448,7 @@
 asExternalBytes
     |sz bytes|
 
-    sz := self size.
+    sz := self byteSize.
     bytes := ExternalBytes unprotectedNew:sz.
     bytes replaceBytesFrom:1 to:sz with:self startingAt:1.
     ^ bytes
@@ -2456,6 +2456,7 @@
     "
       #[1 2 3 4 5 6 7] asExternalBytes
       'Hello World' asExternalBytes
+      'Hello World' asUnicodeString asExternalBytes
     "
 !
 
@@ -2469,10 +2470,9 @@
 
     |bytes sz|
 
-    sz := self size.
-    bytes := ExternalBytes basicNew allocateBytes:(sz + 1).
+    sz := self byteSize.
+    bytes := ExternalBytes basicNew allocateBytes:sz.
     bytes replaceFrom:1 to:sz with:self startingAt:1.
-    bytes at:(sz + 1) put:0.
     ^ bytes
 
     "
@@ -2481,7 +2481,7 @@
      ObjectMemory garbageCollect
     "
 
-    "Created: / 05-06-2012 / 13:25:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Created: / 05-06-2012 / 14:11:35 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !UninterpretedBytes methodsFor:'filling & replacing'!
@@ -2505,7 +2505,7 @@
 
 #ifndef NO_PRIM_BYTEARR
     if ((__isBytes(aCollection) || __isExternalBytesLike(aCollection))
-     && __isBytes(self)
+     && (__isBytes(self) || __isWords(self))
      && __bothSmallInteger(start, stop)
      && __isSmallInteger(repStart)) {
 	startIndex = __intVal(start) - 1;
@@ -2720,14 +2720,14 @@
      therefore the change may affect all others referencing the receiver."
 
     ^ self
-        replaceBytesFrom:1
-        to:(replacementCollection size min:self size)
-        with:replacementCollection
-        startingAt:1
+	replaceBytesFrom:1
+	to:(replacementCollection size min:self size)
+	with:replacementCollection
+	startingAt:1
 
     "
-     (ByteArray new:10) replaceBytesWith:'hello'    
-     (ByteArray new:10) replaceBytesWith:'hello world bla bla bla'    
+     (ByteArray new:10) replaceBytesWith:'hello'
+     (ByteArray new:10) replaceBytesWith:'hello world bla bla bla'
     "
 
     "Created: / 09-01-2012 / 16:18:10 / cg"
@@ -2958,13 +2958,13 @@
 !UninterpretedBytes class methodsFor:'documentation'!
 
 version
-    ^ '$Id: UninterpretedBytes.st 10812 2012-06-05 12:18:28Z vranyj1 $'
+    ^ '$Id: UninterpretedBytes.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/UninterpretedBytes.st,v 1.84 2012/04/03 14:25:21 stefan Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/UninterpretedBytes.st,v 1.89 2012/06/05 12:29:47 vrany Exp §'
 !
 
 version_SVN
-    ^ '$Id: UninterpretedBytes.st 10812 2012-06-05 12:18:28Z vranyj1 $'
+    ^ '$Id: UninterpretedBytes.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !
--- a/UserPreferences.st	Tue Jun 05 13:18:28 2012 +0100
+++ b/UserPreferences.st	Tue Jun 05 14:35:12 2012 +0100
@@ -3549,6 +3549,30 @@
     "Modified: / 11.9.1998 / 00:09:59 / cg"
 !
 
+showTypeIndicatorInInspector
+    ^ self at:#showTypeIndicatorInInspector ifAbsent:true
+
+    "
+     UserPreferences current showTypeIndicatorInInspector
+    "
+
+    "Created: / 16-05-2012 / 19:09:50 / cg"
+!
+
+showTypeIndicatorInInspector:aBooleanOrNil
+    ^ self at:#showTypeIndicatorInInspector put:aBooleanOrNil
+
+    "
+     UserPreferences current showTypeIndicatorInInspector:false.
+     NewLauncher inspect.
+
+     UserPreferences current showTypeIndicatorInInspector:true.
+     NewLauncher inspect.
+    "
+
+    "Created: / 16-05-2012 / 19:10:13 / cg"
+!
+
 toolbarVisibleInWorkspace
     "return the flag which defaults the toolbar-visibility in a workspace application"
 
@@ -3957,13 +3981,13 @@
 !UserPreferences class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.306 2012/03/17 10:18:59 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.307 2012/05/16 19:31:45 cg Exp $'
 !
 
 version_CVS
-    ^ '§Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.306 2012/03/17 10:18:59 cg Exp §'
+    ^ '§Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.307 2012/05/16 19:31:45 cg Exp §'
 !
 
 version_SVN
-    ^ '$Id: UserPreferences.st 10796 2012-03-29 14:24:59Z vranyj1 $'
+    ^ '$Id: UserPreferences.st 10814 2012-06-05 13:35:12Z vranyj1 $'
 ! !