Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Sat, 26 Mar 2016 07:56:10 +0000
branchjv
changeset 19478 1f5aa87f6170
parent 19477 af82888ceb72 (current diff)
parent 19476 a4c6bb123422 (diff)
child 19496 7613c0fb5f3c
Merge
ApplicationDefinition.st
ArithmeticValue.st
ArrayedCollection.st
Behavior.st
Block.st
CharacterArray.st
CharacterEncoder.st
CheapBlock.st
Collection.st
CompiledCode.st
Context.st
Date.st
Dictionary.st
ExceptionHandlerSet.st
Filename.st
Geometric.st
HashStream.st
Integer.st
Interval.st
KeyedCollection.st
LibraryDefinition.st
LookupKey.st
Magnitude.st
Method.st
Number.st
Object.st
Point.st
Process.st
Project.st
ProjectDefinition.st
ReadStream.st
SequenceableCollection.st
SignalSet.st
Smalltalk.st
Stream.st
StringCollection.st
Symbol.st
UninterpretedBytes.st
UserPreferences.st
WriteStream.st
--- a/ApplicationDefinition.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/ApplicationDefinition.st	Sat Mar 26 07:56:10 2016 +0000
@@ -100,12 +100,13 @@
 appSourcesProjects
     "Returns only the application projects (which are included in the application module)"
 
-    ^ self effectivePreRequisites select:[:each | 
-        (self moduleFor: each) = self module
-    ].
+    ^ self effectivePreRequisites 
+        select:[:each | 
+            (self moduleFor: each) = self module
+        ].
 
     "
-        bosch_dapasx_application appSourcesProjects
+     bosch_dapasx_application appSourcesProjects
     "
 !
 
@@ -1633,7 +1634,6 @@
 !
 
 generateSubProjectLines_bc_dot_mak         
-
     ^ String streamContents:[:s |
         self effectiveSubProjects do:[:projectID |
             |mappings newObjectLine|
@@ -1678,18 +1678,14 @@
 !
 
 generateSubProjectLines_modules_dot_stx
-    |string|
-
-    string := String streamContents:[:s |
+    ^ String streamContents:[:s |
         self effectiveSubProjects do:[:projectID |
-                    (self shouldBeLoadedInitially:projectID) ifFalse:[
-                        s nextPut:$*.
-                    ].
-                    s nextPutLine:(self libraryNameFor:projectID).
-                ].
+            (self shouldBeLoadedInitially:projectID) ifFalse:[
+                s nextPut:$*.
             ].
-
-    ^ string
+            s nextPutLine:(self libraryNameFor:projectID).
+        ].
+    ].
 
     "
      exept_expecco_application generateSubProjectLines_modules_dot_stx
@@ -3097,6 +3093,10 @@
     "
 !
 
+isAbstract
+    ^ self == ApplicationDefinition
+!
+
 projectType
     ^ self isGUIApplication
         ifTrue:[ GUIApplicationType  ]
@@ -3152,10 +3152,6 @@
 
 !ApplicationDefinition class methodsFor:'testing'!
 
-isAbstract
-    ^ self == ApplicationDefinition
-!
-
 isApplicationDefinition
     ^ self isAbstract not
 
--- a/ArithmeticValue.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/ArithmeticValue.st	Sat Mar 26 07:56:10 2016 +0000
@@ -246,11 +246,12 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for ArithmeticValue here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == ArithmeticValue
 ! !
 
+
 !ArithmeticValue methodsFor:'arithmetic'!
 
 * something
--- a/ArrayedCollection.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/ArrayedCollection.st	Sat Mar 26 07:56:10 2016 +0000
@@ -325,7 +325,7 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for ArrayedCollection here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == ArrayedCollection
 ! !
--- a/Behavior.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Behavior.st	Sat Mar 26 07:56:10 2016 +0000
@@ -3578,7 +3578,12 @@
     "true if this is an abstract class 
      (has no direct instances, should not be instantiated).
      Usually, this means that it only provides shared protocol for its
-     subclasses, which should be used."
+     subclasses, which should be used.
+     Notice: this does not have any semantic effect;
+     it is purely for the browser (shows an 'A'-Indicator) 
+     and for documentation.
+     To enforce abstractness, a subclass should redefine new, to raise an exception.
+     (which some do, but many are too lazy to do)"
     
     ^ false
 !
--- a/Block.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Block.st	Sat Mar 26 07:56:10 2016 +0000
@@ -527,7 +527,7 @@
 
 ifError:handlerBlock
     "squeak compatibility:
-     Evaluate the recevier block and return its value, if no error occurs.
+     Evaluate the receiver block and return its value, if no error occurs.
      If an error is raised, return the value from handlerBlock.
      The handlerBlock may take 0,1 or 2 args.
      (1 arg  -> the exception;
@@ -682,21 +682,21 @@
 !Block methodsFor:'accessing'!
 
 home
-    "return the receivers home context (the context where it was
+    "return the receiver's home context (the context where it was
      created). For cheap blocks, nil is returned"
 
     ^ home
 !
 
 homeMethod
-    "return the receivers home method.
-     Thats the method where the block was created."
+    "return the receiver's home method.
+     That's the method where the block was created."
 
     |m|
 
     home notNil ifTrue:[
-	m := home method.
-	m notNil ifTrue:[^ m].
+        m := home method.
+        m notNil ifTrue:[^ m].
     ].
     m := self literalAt:1 ifAbsent:nil.
     m isMethod ifTrue:[^ m].
@@ -706,7 +706,7 @@
 !
 
 method
-    "return the receivers method
+    "return the receiver's method
      (the method where the block was created).
      Obsolete: use #homeMethod for ST80 compatibility."
 
@@ -858,7 +858,7 @@
 
     Transcript show:anInfoString.
     micros < 1000 ifTrue:[
-	Transcript show:micros; show:' µs'.
+	Transcript show:micros; show:' s'.
     ] ifFalse:[
 	micros < 100000 ifTrue:[
 	    millis := (micros / 1000.0) asFixedPointRoundedToScale:2.
--- a/CharacterArray.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/CharacterArray.st	Sat Mar 26 07:56:10 2016 +0000
@@ -755,7 +755,7 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for CharacterArray here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == CharacterArray
 !
@@ -3241,7 +3241,8 @@
 !
 
 asMutator
-    "return a corresponding setter method's selector"
+    "return a corresponding setter method's selector.
+     I.e. #foo asMutator returns #foo:"
 
     ^ (self asOneByteString,':') asSymbol
 !
@@ -3763,7 +3764,7 @@
 !
 
 chopTo:maxLen
-    "if the receivers size is less or equal to maxLen, return it.
+    "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      in the middle have been removed for a total string length
      of maxLen."
@@ -3774,7 +3775,7 @@
 
     n1 := n2 := maxLen // 2.
     maxLen odd ifTrue:[
-	n2 := n1 + 1
+        n2 := n1 + 1
     ].
     ^ (self copyFrom:1 to:n1) , (self copyFrom:sz - n2 + 1)
 
@@ -3790,7 +3791,7 @@
 !
 
 contractAtBeginningTo:maxLen
-    "if the receivers size is less or equal to maxLen, return it.
+    "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      at the beginning have been replaced by '...' for a total string length
      of maxLen. Can be used to abbreviate long entries in tables."
@@ -3813,7 +3814,7 @@
 !
 
 contractAtEndTo:maxLen
-    "if the receivers size is less or equal to maxLen, return it.
+    "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      at the end have been replaced by '...' for a total string length
      of maxLen. Can be used to abbreviate long entries in tables."
@@ -3836,7 +3837,7 @@
 !
 
 contractLeftTo:maxLen
-    "if the receivers size is less or equal to maxLen, return it.
+    "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      near the first quarter have been replaced by '...' for a total string length
      of maxLen.
@@ -3867,7 +3868,7 @@
 !
 
 contractTo:maxLen
-    "if the receivers size is less or equal to maxLen, return it.
+    "if the receiver's size is less or equal to maxLen, return it.
      Otherwise, return a copy of the receiver, where some characters
      in the middle have been replaced by '...' for a total string length
      of maxLen. Can be used to abbreviate long entries in tables."
@@ -3950,7 +3951,7 @@
 !
 
 copyWith:aCharacter
-    "return a new string containing the receivers characters
+    "return a new string containing the receiver's characters
      and the single new character, aCharacter.
      This is different from concatentation, which expects another string
      as argument, but equivalent to copy-and-addLast.
@@ -3960,11 +3961,11 @@
     |sz newString|
 
     aCharacter bitsPerCharacter > self bitsPerCharacter ifTrue:[
-	sz := self size.
-	newString := aCharacter stringSpecies new:sz + 1.
-	newString replaceFrom:1 to:sz with:self startingAt:1.
-	newString at:sz+1 put:aCharacter.
-	^ newString.
+        sz := self size.
+        newString := aCharacter stringSpecies new:sz + 1.
+        newString replaceFrom:1 to:sz with:self startingAt:1.
+        newString at:sz+1 put:aCharacter.
+        ^ newString.
     ].
     ^ super copyWith:aCharacter
 !
@@ -5163,11 +5164,11 @@
 !CharacterArray methodsFor:'padded copying'!
 
 centerPaddedTo:newSize
-     "return a new string consisting of the receivers characters,
-     plus spaces up to length and center the receivers characters in
-     the resulting string.
-     If the receivers size is equal or greater than the length argument,
-     the original receiver is returned unchanged."
+     "return a new string consisting of the receiver's characters,
+      plus spaces up to length and center the receiver's characters in
+      the resulting string.
+      If the receiver's size is equal or greater than the length argument,
+      the original receiver is returned unchanged."
 
      ^ self centerPaddedTo:newSize with:(Character space)
 
@@ -5183,16 +5184,16 @@
     "return a new string of length size, which contains the receiver
      centered (i.e. padded on both sides).
      Characters are filled with padCharacter.
-     If the receivers size is equal or greater than the length argument,
+     If the receiver's size is equal or greater than the length argument,
      the original receiver is returned unchanged."
 
     |len s|
 
     len := self size.
     (len < size) ifTrue:[
-	s := self species new:size withAll:padCharacter.
-	s replaceFrom:(size - len) // 2  + 1 with:self.
-	^ s
+        s := self species new:size withAll:padCharacter.
+        s replaceFrom:(size - len) // 2  + 1 with:self.
+        ^ s
     ]
 
     "
@@ -5211,16 +5212,16 @@
      aligned at the decimal-period column and afterPeriod characters to the right
      of the period. The periodCharacter is passed as arguments (allowing for US and European formats
      to be padded).
-     If the receivers size is equal or greater than the length argument,
+     If the receiver's size is equal or greater than the length argument,
      the original receiver is returned unchanged.
      (sounds complicated ? -> see examples below)."
 
     ^ self
-	decimalPaddedTo:size
-	and:afterPeriod
-	at:decimalCharacter
-	withLeft:(Character space)
-	right:$0
+        decimalPaddedTo:size
+        and:afterPeriod
+        at:decimalCharacter
+        withLeft:(Character space)
+        right:$0
 
     "
      '123' decimalPaddedTo:10 and:3 at:$.      -> '   123    '
@@ -5241,7 +5242,7 @@
      Characters on the left are filled with leftPadChar.
      If rightPadChar is nil, characters on the right are filled with leftPadCharacter too;
      otherwise, if missing, a decimal point is added and right characters filled with this.
-     If the receivers size is equal or greater than the length argument,
+     If the receiver's size is equal or greater than the length argument,
      the original receiver is returned unchanged.
      (sounds complicated ? -> see examples below)."
 
@@ -5249,25 +5250,25 @@
 
     idx := self indexOf:decimalCharacter.
     idx == 0 ifTrue:[
-	"/
-	"/ no decimal point found; adjust string to the left of the period column
-	"/
-	rightPadChar isNil ifTrue:[
-	    s := self , (self species new:afterPeriod + 1 withAll:leftPadChar)
-	] ifFalse:[
-	    s:= self , decimalCharacter asString , (self species new:afterPeriod withAll:rightPadChar).
-	].
+        "/
+        "/ no decimal point found; adjust string to the left of the period column
+        "/
+        rightPadChar isNil ifTrue:[
+            s := self , (self species new:afterPeriod + 1 withAll:leftPadChar)
+        ] ifFalse:[
+            s:= self , decimalCharacter asString , (self species new:afterPeriod withAll:rightPadChar).
+        ].
     ] ifFalse:[
 
-	"/ the number of after-decimalPoint characters
-	n := self size - idx.
-	rest := afterPeriod - n.
-	rest > 0 ifTrue:[
-	    s := (self species new:rest withAll:(rightPadChar ? leftPadChar)).
-	] ifFalse:[
-	    s := ''
-	].
-	s := self , s.
+        "/ the number of after-decimalPoint characters
+        n := self size - idx.
+        rest := afterPeriod - n.
+        rest > 0 ifTrue:[
+            s := (self species new:rest withAll:(rightPadChar ? leftPadChar)).
+        ] ifFalse:[
+            s := ''
+        ].
+        s := self , s.
     ].
 
     ^ s leftPaddedTo:size with:leftPadChar
@@ -5288,7 +5289,7 @@
     "return a new string of length size, which contains the receiver
      right-adjusted (i.e. padded on the left).
      Characters on the left are filled with spaces.
-     If the receivers size is equal or greater than the length argument,
+     If the receiver's size is equal or greater than the length argument,
      the original receiver is returned unchanged."
 
     ^ self leftPaddedTo:size with:(Character space)
@@ -5303,7 +5304,7 @@
 paddedTo:newSize
      "return a new string consisting of the receivers characters,
      plus spaces up to length.
-     If the receivers size is equal or greater than the length argument,
+     If the receiver's size is equal or greater than the length argument,
      the original receiver is returned unchanged."
 
      ^ self paddedTo:newSize with:(Character space)
@@ -5655,7 +5656,7 @@
 !
 
 heightOn:aGC
-    "return the size of the recevier in device units if displayed on aGC"
+    "return the size of the receiver in device units if displayed on aGC"
 
     ^ (aGC font onDevice:aGC device) heightOf:self
 
@@ -5741,7 +5742,7 @@
 leftIndent
     "if the receiver starts with spaces, return the number of spaces
      at the left - otherwise, return 0.
-     If the receiver consists of spaces only, return the receivers size."
+     If the receiver consists of spaces only, return the receiver's size."
 
     |index "{Class: SmallInteger }"
      end   "{Class: SmallInteger }"|
@@ -5749,8 +5750,8 @@
     index := 1.
     end := self size.
     [index <= end] whileTrue:[
-	(self at:index) isSeparator ifFalse:[^ index - 1].
-	index := index + 1
+        (self at:index) isSeparator ifFalse:[^ index - 1].
+        index := index + 1
     ].
     ^ end
 
@@ -5812,7 +5813,7 @@
 !
 
 widthFrom:startIndex to:endIndex on:aGC
-    "return ths size of part of the recevier in device units if displayed on aGC"
+    "return ths size of part of the receiver in device units if displayed on aGC"
 
     ^ (aGC font onDevice:aGC device) widthOf:self from:startIndex to:endIndex
 
@@ -5823,7 +5824,7 @@
 !
 
 widthOn:aGC
-    "return ths size of the recevier in device units if displayed on aGC"
+    "return ths size of the receiver in device units if displayed on aGC"
 
     ^ (aGC font onDevice:aGC device) widthOf:self
 
@@ -6386,13 +6387,13 @@
 !
 
 withTabs
-    "return a string consisting of the receivers characters
+    "return a string consisting of the receiver's characters
      where leading spaces are replaced by tabulator characters (assuming 8-col tabs).
      Notice: if the receiver does not contain any tabs, it is returned unchanged;
      otherwise a new string is returned.
      Limitation: only the very first spaces are replaced
-		 (i.e. if the receiver contains newLine characters,
-		  no tabs are inserted after those lineBreaks)"
+                 (i.e. if the receiver contains newLine characters,
+                  no tabs are inserted after those lineBreaks)"
 
     |idx   "{ SmallInteger }"
      nTabs "{ SmallInteger }"
@@ -6419,7 +6420,7 @@
 !
 
 withTabsExpanded
-    "return a string consisting of the receivers characters,
+    "return a string consisting of the receiver's characters,
      where all tabulator characters are expanded into spaces (assuming 8-col tabs).
      Notice: if the receiver does not contain any tabs, it is returned unchanged;
      otherwise a new string is returned.
@@ -6436,26 +6437,26 @@
      ('123456789' , Character tab asString , 'x') withTabsExpanded
 
      (String with:Character tab
-	     with:Character tab
-	     with:$1) withTabsExpanded
+             with:Character tab
+             with:$1) withTabsExpanded
 
      (String with:Character tab
-	     with:$1
-	     with:Character tab
-	     with:$2) withTabsExpanded
+             with:$1
+             with:Character tab
+             with:$2) withTabsExpanded
 
      (String with:Character tab
-	     with:$1
-	     with:Character cr
-	     with:Character tab
-	     with:$2) withTabsExpanded
+             with:$1
+             with:Character cr
+             with:Character tab
+             with:$2) withTabsExpanded
     "
 
     "Modified: 12.5.1996 / 13:05:10 / cg"
 !
 
 withTabsExpanded:numSpaces
-    "return a string consisting of the receivers characters,
+    "return a string consisting of the receiver's characters,
      where all tabulator characters are expanded into spaces (assuming numSpaces-col tabs).
      Notice: if the receiver does not contain any tabs, it is returned unchanged;
      otherwise a new string is returned.
@@ -6477,19 +6478,19 @@
 
     col := 1. newSz := 0.
     1 to:sz do:[:srcIdx |
-	ch := self at:srcIdx.
-	ch == Character tab ifFalse:[
-	    col := col + 1.
-	    newSz := newSz + 1.
-	    ch == Character cr ifTrue:[
-		col := 1
-	    ].
-	] ifTrue:[
-	    (col \\ numSpaces) to:numSpaces do:[:ii |
-		newSz := newSz + 1.
-		col := col + 1
-	    ].
-	]
+        ch := self at:srcIdx.
+        ch == Character tab ifFalse:[
+            col := col + 1.
+            newSz := newSz + 1.
+            ch == Character cr ifTrue:[
+                col := 1
+            ].
+        ] ifTrue:[
+            (col \\ numSpaces) to:numSpaces do:[:ii |
+                newSz := newSz + 1.
+                col := col + 1
+            ].
+        ]
     ].
 
     self isText ifTrue:[ 
@@ -6502,26 +6503,26 @@
 
     col := 1. dstIdx := 1.
     1 to:sz do:[:srcIdx |
-	ch := self at:srcIdx.
-
-	ch == Character tab ifFalse:[
-	    col := col + 1.
-	    ch == Character cr ifTrue:[
-		col := 1
-	    ].
-	    hasEmphasis ifTrue:[
-		e := self emphasisAt:srcIdx.
-		str emphasisAt:dstIdx put:e
-	    ].
-	    str at:dstIdx put:ch.
-	    dstIdx := dstIdx + 1
-	] ifTrue:[
-	    (col \\ numSpaces) to:numSpaces do:[:ii |
-		str at:dstIdx put:Character space.
-		dstIdx := dstIdx + 1.
-		col := col + 1
-	    ].
-	]
+        ch := self at:srcIdx.
+
+        ch == Character tab ifFalse:[
+            col := col + 1.
+            ch == Character cr ifTrue:[
+                col := 1
+            ].
+            hasEmphasis ifTrue:[
+                e := self emphasisAt:srcIdx.
+                str emphasisAt:dstIdx put:e
+            ].
+            str at:dstIdx put:ch.
+            dstIdx := dstIdx + 1
+        ] ifTrue:[
+            (col \\ numSpaces) to:numSpaces do:[:ii |
+                str at:dstIdx put:Character space.
+                dstIdx := dstIdx + 1.
+                col := col + 1
+            ].
+        ]
     ].
     ^ str
 
@@ -6535,19 +6536,19 @@
      ('123456789' , Character tab asString , 'x') withTabsExpanded
 
      (String with:Character tab
-	     with:Character tab
-	     with:$1) withTabsExpanded
+             with:Character tab
+             with:$1) withTabsExpanded
 
      (String with:Character tab
-	     with:$1
-	     with:Character tab
-	     with:$2) withTabsExpanded
+             with:$1
+             with:Character tab
+             with:$2) withTabsExpanded
 
      (String with:Character tab
-	     with:$1
-	     with:Character cr
-	     with:Character tab
-	     with:$2) withTabsExpanded
+             with:$1
+             with:Character cr
+             with:Character tab
+             with:$2) withTabsExpanded
     "
 
     "Modified: / 12-05-1996 / 13:05:10 / cg"
@@ -6709,7 +6710,7 @@
 !
 
 withoutCRs
-    "return a new collection consisting of receivers elements
+    "return a new collection consisting of receiver's elements
      with all cr-characters replaced by \-characters.
      This is the reverse operation of withCRs."
 
@@ -7534,19 +7535,19 @@
 !
 
 isValidSmalltalkIdentifier
-    "return true, if the receivers characters make up a valid smalltalk identifier"
+    "return true, if the receiver's characters make up a valid smalltalk identifier"
 
     |scanner tok|
 
     scanner := Compiler new.
     scanner source:(self readStream).
     Parser parseErrorSignal handle:[:ex |
-	tok := nil.
+        tok := nil.
     ] do:[
-	tok := scanner nextToken.
+        tok := scanner nextToken.
     ].
     tok ~~ #Identifier ifTrue:[
-	^ false
+        ^ false
     ].
     scanner tokenPosition == 1 ifFalse:[^ false].
     ^ scanner sourceStream atEnd.
--- a/CharacterEncoder.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/CharacterEncoder.st	Sat Mar 26 07:56:10 2016 +0000
@@ -18,7 +18,7 @@
 	classVariableNames:'EncoderClassesByName EncodersByName CachedEncoders AccessLock
 		NullEncoderInstance Jis7KanjiEscapeSequence
 		Jis7RomanEscapeSequence JisISO2022EscapeSequence
-		Jis7KanjiOldEscapeSequence'
+		Jis7KanjiOldEscapeSequence EncodingDetectors'
 	poolDictionaries:''
 	category:'Collections-Text-Encodings'
 !
@@ -977,6 +977,14 @@
 
 !CharacterEncoder class methodsFor:'queries'!
 
+isAbstract
+    "Return if this class is an abstract class.
+     True is returned for CharacterEncoder here; false for subclasses.
+     Abstract subclasses must redefine this again."
+
+    ^ self == CharacterEncoder
+!
+
 isEncoding:subSetEncodingArg subSetOf:superSetEncodingArg
     "return true, if superSetEncoding encoding includes all characters of subSetEncoding.
      (this means: characters are included - not that they have the same encoding)"
@@ -1080,131 +1088,31 @@
     ^ self nameOfEncoding asUppercaseFirst
 ! !
 
-!CharacterEncoder class methodsFor:'testing'!
-
-isAbstract
-    "Return if this class is an abstract class.
-     True is returned for CharacterEncoder here; false for subclasses.
-     Abstract subclasses must redefine again."
-
-    ^ self == CharacterEncoder
-! !
-
 !CharacterEncoder class methodsFor:'utilities'!
 
 guessEncodingOfBuffer:buffer
-    "look for a string of the form
+    "try to guess a string-buffer's encoding.
+     Basically looks for a string of the form
             encoding #name
      or:
             encoding: name
      within the given buffer 
-     (which is usually the first few bytes of a textFile)."
-
-    |lcBuffer quote peek|
+     (which is usually within the first few bytes of a textFile)."
 
     buffer size < 4 ifTrue:[
         "not enough bytes to determine the contents"
         ^ nil.
     ].
-
-    "check the Byte Order Mark (BOM)"
-    peek := (buffer at:1) codePoint.
-    peek < 16rFE ifTrue:[
-        (peek = 16rEF
-            and:[(buffer at:2) codePoint = 16rBB 
-            and:[(buffer at:3) codePoint = 16rBF]]) ifTrue:[
-            ^ #utf8
-        ].
-        (peek = 0 
-            and:[(buffer at:2) codePoint = 0 
-            and:[(buffer at:3) codePoint = 16rFE 
-            and:[(buffer at:4) codePoint = 16rFF]]]) ifTrue:[
-            ^ #utf32be
-        ].
-    ] ifFalse:[
-        peek = 16rFF ifTrue:[
-            (buffer at:2) codePoint = 16rFE ifTrue:[
-                "little endian"
-                ((buffer at:3) codePoint = 0 and:[(buffer at:4) codePoint = 0]) ifTrue:[
-                    ^ #utf32le.   
-                ].
-                ^ #utf16le
-            ].
-        ] ifFalse:["peek = 16rFE"
-            (buffer at:2) codePoint = 16rFF ifTrue:[
-                "big endian"
-                ^ #utf16be
-            ].
-        ]
-    ].
-
-    lcBuffer := buffer asLowercase.
-
-    "now look for an inline encoding markup"
-    #(charset encoding) do:[:keyWord |
-        |encoderOrNil idx s w enc|
-
-        (idx := lcBuffer findString:keyWord) ~~ 0 ifTrue:[
-            s := ReadStream on:buffer.
-            s position:idx-1.
-            s skip:keyWord size.
-            s skipSeparators. 
-
-            "do not include '=' here, otherwise
-             files containing xml code (<?xml charset='utf8'> will be parsed as UTF-8"
+    EncodingDetectors isNil ifTrue:[
+        self initializeEncodingDetectors.
+    ].    
+    EncodingDetectors do:[:each |
+        |guess|
 
-            [':#=' includes:s peek] whileTrue:[
-                s next.
-                s skipSeparators. 
-            ].
-            s skipSeparators.
-            ('"''' includes:s peek) ifTrue:[
-                quote := s next.
-                w := s upTo:quote.
-            ] ifFalse:[
-                w := s upToElementForWhich:[:ch | ch isSeparator or:[ch == $" or:[ch == $' or:[ch == $> ]]]].
-            ].
-            w notNil ifTrue:[
-                enc := w withoutQuotes.
-                (enc startsWith:'x-') ifTrue:[
-                    enc := enc copyFrom:3.
-                ].
-                encoderOrNil := self encoderFor:enc ifAbsent:nil.
-                encoderOrNil notNil ifTrue:[
-                    ^ encoderOrNil nameOfEncoding
-                ].
-"/                enc size >=3 ifTrue:[
-"/                    Transcript showCR:'Unknown encoding: ' , (withoutQuotes value:w).
-"/                ]
-            ].
+        (guess := each value:buffer) notNil ifTrue:[
+            ^ guess
         ].
-    ].
-
-    "/ look for JIS7 / EUC encoding
-    (buffer findString:self jisISO2022EscapeSequence) ~~ 0 ifTrue:[
-        ^ #'iso2020-jp'
-    ].
-    (buffer findString:self jis7KanjiEscapeSequence) ~~ 0 ifTrue:[
-        ^ #jis7
-    ].
-    (buffer findString:self jis7KanjiOldEscapeSequence) ~~ 0 ifTrue:[
-        ^ #jis7
-    ].
-
-    "/ TODO:
-
-"/    "/ look for EUC
-"/    idx := aString findFirst:[:char | |ascii|
-"/                                        ((ascii := char asciiValue) >= 16rA1)     
-"/                                        and:[ascii <= 16rFE]].
-"/    idx ~~ 0 ifTrue:[
-"/        ascii := (aString at:(idx + 1)) asciiValue.
-"/        (ascii >= 16rA1 and:[ascii <= 16rFE]) ifTrue:[
-"/            ^ #euc
-"/        ]
-"/    ].
-    "/ look for SJIS ...
-
+    ].    
     ^ nil
 !
 
@@ -1259,6 +1167,148 @@
     "Modified: / 31-05-2011 / 15:45:23 / cg"
 !
 
+initializeEncodingDetectors
+    "setup the list of encoding detectors.
+     This is a list of blocks, which get a buffer as argument,
+     and return an encoding symbol or nil.
+     Can be customized for more detectors 
+     (used to be hard-coded in guessEncodingOfBuffer:)"
+
+    EncodingDetectors := OrderedCollection new.
+
+    "check for Unicode Byte Order Marks (BOM)"
+    EncodingDetectors
+        add:[:buffer |
+            |guess byte1 byte2|
+            
+            byte1 := (buffer at:1) codePoint.
+            byte2 := (buffer at:2) codePoint.
+            byte1 < 16rFE ifTrue:[
+                (byte1 = 16rEF
+                    and:[byte2 = 16rBB 
+                    and:[(buffer at:3) codePoint = 16rBF]]) ifTrue:[
+                    guess := #utf8
+                ] ifFalse:[
+                    (byte1 = 0 
+                        and:[byte2 = 0 
+                        and:[(buffer at:3) codePoint = 16rFE 
+                        and:[(buffer at:4) codePoint = 16rFF]]]) ifTrue:[
+                        "00-00-FE-FF big endian utf32"
+                        guess := #utf32be
+                    ].
+                ]    
+            ] ifFalse:[
+                byte1 = 16rFF ifTrue:[
+                    byte2 = 16rFE ifTrue:[
+                        "FF-FE little endian utf16 or utf32"
+                        ((buffer at:3) codePoint = 0 and:[(buffer at:4) codePoint = 0]) ifTrue:[
+                            "FF-FE-00-00 little endian utf32"
+                            guess := #utf32le.   
+                        ] ifFalse:[
+                            guess := #utf16le
+                        ]    
+                    ].
+                ] ifFalse:["byte1 = 16rFE"
+                    "FE-FF big endian utf16"
+                    byte2 = 16rFF ifTrue:[
+                        "big endian"
+                        guess := #utf16be
+                    ].
+                ]
+            ].
+            guess
+        ].
+        
+    "check for an inline encoding markup (charset= / encoding=) substring"
+    EncodingDetectors
+        add:[:buffer |
+            |guess lcBuffer quote peek|
+
+            lcBuffer := buffer asLowercase.
+
+            guess :=
+                #(charset encoding) doWithExit:[:keyWord :exit |
+                    |encoderOrNil idx s w enc|
+
+                    guess isNil ifTrue:[
+                    (idx := lcBuffer findString:keyWord) ~~ 0 ifTrue:[
+                        s := ReadStream on:buffer.
+                        s position:idx-1.
+                        s skip:keyWord size.
+                        s skipSeparators. 
+
+                        "do not include '=' here, otherwise
+                         files containing xml code (<?xml charset='utf8'> will be parsed as UTF-8"
+
+                        [':#=' includes:s peek] whileTrue:[
+                            s next.
+                            s skipSeparators. 
+                        ].
+                        s skipSeparators.
+                        ('"''' includes:s peek) ifTrue:[
+                            quote := s next.
+                            w := s upTo:quote.
+                        ] ifFalse:[
+                            w := s upToElementForWhich:[:ch | ch isSeparator or:[ch == $" or:[ch == $' or:[ch == $> ]]]].
+                        ].
+                        w notNil ifTrue:[
+                            enc := w withoutQuotes.
+                            (enc startsWith:'x-') ifTrue:[
+                                enc := enc copyFrom:3.
+                            ].
+                            encoderOrNil := self encoderFor:enc ifAbsent:nil.
+                            encoderOrNil notNil ifTrue:[
+                                exit value:(encoderOrNil nameOfEncoding)
+                            ].
+                        ].
+                    ].
+                ].
+                nil
+            ].
+            guess
+        ].
+        
+    "/ check for JIS7 encoding
+    EncodingDetectors
+        add:[:buffer |
+            (buffer findString:self jisISO2022EscapeSequence) ~~ 0 ifTrue:[
+                #'iso2020-jp'
+            ] ifFalse:[
+                (buffer findString:self jis7KanjiEscapeSequence) ~~ 0 ifTrue:[
+                    #jis7
+                ] ifFalse:[
+                    (buffer findString:self jis7KanjiOldEscapeSequence) ~~ 0 ifTrue:[
+                        #jis7
+                    ] ifFalse:[
+                        nil
+                    ]
+                ]
+            ]    
+        ].
+
+    "/ TODO: look for EUC, SJIS etc.
+    "/ Disabled, due to too many false positives.
+    "/ if required, think about it, fix it and uncomment it
+"/    EncodingDetectors
+"/        add:[:buffer |
+"/            |guess idx|
+"/
+"/            idx := buffer 
+"/                        findFirst:[:char | 
+"/                            |code|
+"/                            code := char codePoint.
+"/                            code between:16rA1 and: 16rFE
+"/                        ].
+"/            ((idx ~~ 0) 
+"/                and:[ (buffer at:(idx + 1)) codePoint between:16rA1 and: 16rFE ])
+"/            ifTrue:[
+"/                guess := #euc
+"/            ] ifFalse:[
+"/                "/ look for SJIS ...
+"/            ]
+"/        ].
+!
+
 showCharacterSet
     |font|
 
@@ -1274,6 +1324,15 @@
 
     "
      CharacterEncoderImplementations::MS_Ansi showCharacterSet
+     CharacterEncoderImplementations::ISO8859_1 showCharacterSet
+     CharacterEncoderImplementations::ISO8859_2 showCharacterSet
+     CharacterEncoderImplementations::ISO8859_3 showCharacterSet
+     CharacterEncoderImplementations::ISO8859_4 showCharacterSet
+     CharacterEncoderImplementations::ISO8859_5 showCharacterSet
+     CharacterEncoderImplementations::ISO8859_6 showCharacterSet
+     CharacterEncoderImplementations::ISO8859_7 showCharacterSet
+     CharacterEncoderImplementations::ISO8859_8 showCharacterSet
+     CharacterEncoderImplementations::ISO8859_9 showCharacterSet
     "
 ! !
 
--- a/CheapBlock.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/CheapBlock.st	Sat Mar 26 07:56:10 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Block variableSubclass:#CheapBlock
 	instanceVariableNames:'selfValue method'
 	classVariableNames:''
@@ -85,8 +87,8 @@
 !CheapBlock methodsFor:'accessing'!
 
 homeMethod
-    "return the receivers home method.
-     Thats the method where the block was created."
+    "return the receiver's home method.
+     That's the method where the block was created."
 
     ^ method
 
@@ -95,8 +97,8 @@
 !
 
 method
-    "return the receivers home method.
-     Thats the method where the block was created.
+    "return the receiver's home method.
+     That's the method where the block was created.
      Obsolete: use #homeMethod for ST80 compatibility."
 
     ^ method
@@ -111,7 +113,7 @@
 !
 
 setMethod:aMethod
-    "set the receivers home method.
+    "set the receiver's home method.
      This is a private entry for the compiler"
 
     method := aMethod
@@ -187,6 +189,6 @@
 !CheapBlock class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CheapBlock.st,v 1.22 2014-11-06 05:30:07 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/Collection.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Collection.st	Sat Mar 26 07:56:10 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
               All Rights Reserved
@@ -277,6 +275,7 @@
     ^ self newWithSize:n
 ! !
 
+
 !Collection class methodsFor:'Signal constants'!
 
 emptyCollectionSignal
@@ -333,7 +332,7 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for Collection here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == Collection
 ! !
@@ -491,6 +490,8 @@
 !
 
 ifEmpty:ifEmptyValue ifNotEmpty:ifNotEmptyValue
+    "return ifNotEmptyValue if not empty, ifEmptyValue otherwise"
+    
     |action|
 
     action := self isEmpty ifTrue:[ ifEmptyValue ] ifFalse:[ ifNotEmptyValue ].
@@ -504,31 +505,44 @@
 !
 
 ifEmpty:ifEmptyValue ifNotEmptyDo:ifNotEmptyValue
+    "return ifNotEmptyValue if not empty, ifEmptyValue otherwise"
+
     ^ self ifEmpty:ifEmptyValue ifNotEmpty:ifNotEmptyValue
 !
 
 ifEmptyDo:ifEmptyValue ifNotEmpty:ifNotEmptyValue
+    "return ifNotEmptyValue if not empty, ifEmptyValue otherwise"
+
     ^ self ifEmpty:ifEmptyValue ifNotEmpty:ifNotEmptyValue
 !
 
 ifNotEmpty:ifNotEmptyValue
+    "return ifNotEmptyValue if not empty, nil otherwise"
+
     ^ self ifEmpty:nil ifNotEmpty:ifNotEmptyValue
 !
 
 ifNotEmptyDo:ifNotEmptyValue
+    "return ifNotEmptyValue if not empty, nil otherwise"
+
     ^ self ifEmpty:nil ifNotEmpty:ifNotEmptyValue
 !
 
 ifNotEmptyDo:ifNotEmptyValue ifEmpty:ifEmptyValue
+    "return ifNotEmptyValue if not empty, ifEmptyValue otherwise"
+
     ^ self ifEmpty:ifEmptyValue ifNotEmpty:ifNotEmptyValue
 !
 
 intersection:aCollection
+    "same as intersect: for Squeak compatibility"
+    
     ^ self intersect:aCollection
 
     "Created: / 22-10-2008 / 21:29:27 / cg"
 ! !
 
+
 !Collection methodsFor:'accessing'!
 
 anElement
@@ -1113,7 +1127,7 @@
      Notice: for some collections (those not tuned for
              resizing themself) this may be very slow.
              If the number of removed elements is big compared to to
-             the receivers size, it may be better to copy the
+             the receiver's size, it may be better to copy the
              ones which are not to be removed into a new collection."
 
     aCollection do:[:element | self remove:element].
@@ -1182,7 +1196,7 @@
      Notice: for some collections (those not tuned for
              resizing themself) this may be very slow.
              If the number of removed elements is big compared to to
-             the receivers size, it may be better to copy the
+             the receiver's size, it may be better to copy the
              ones which are not to be removed into a new collection."
 
     aCollection do:[:element | self removeIdentical:element].
@@ -2617,7 +2631,7 @@
 
 detect:checkBlock thenCompute:evalBlock 
     "evaluate the argument, aBlock for each element in the receiver until
-     chloeckBck returns true; in this case return the value from evalBlock
+     checkBck returns true; in this case return the value from evalBlock
      applied to the element which caused the true evaluation.
      If none of the evaluations returns true, report an error"
 
@@ -2631,7 +2645,7 @@
 
 detect:checkBlock thenCompute:evalBlock ifNone:exceptionValue
     "evaluate the argument, aBlock for each element in the receiver until
-     chloeckBck returns true; in this case return the value from evalBlock
+     checkBck returns true; in this case return the value from evalBlock
      applied to the element which caused the true evaluation.
      If none of the evaluations returns true, return the value from exceptionValue."
 
@@ -2682,9 +2696,9 @@
 
 detectMax: aBlock
     "Evaluate aBlock with each of the receiver's elements as the argument. 
-    Answer the element for which aBlock evaluates to the highest magnitude.
-    If the receiver collection is empty, return nil.  
-    This method might also be called elect:."
+     Answer the element for which aBlock evaluates to the highest magnitude.
+     If the receiver collection is empty, return nil.  
+     This method might also be called elect:."
 
     | maxElement maxValue |
 
@@ -2692,9 +2706,9 @@
         | val |
 
         val := aBlock value: each.
-        "Note that there is no way to get the first element that works 
-        for all kinds of Collections.  
-        Must test every one (maxValue is nil for the first element)."
+        "Note that there is no way to get the first element 
+         which works for all kinds of Collections.  
+         Must therefore test every one (maxValue is nil for the first element)."
         (maxValue == nil or:[val > maxValue]) ifTrue: [
            maxElement := each.
            maxValue := val
@@ -2711,8 +2725,8 @@
 
 detectMin: aBlock
     "Evaluate aBlock with each of the receiver's elements as the argument. 
-    Answer the element for which aBlock evaluates to the lowest number.
-    If the receiver collection is empty, return nil."
+     Answer the element for which aBlock evaluates to the lowest number.
+     If the receiver collection is empty, return nil."
 
     | minElement minValue |
 
@@ -2720,9 +2734,9 @@
         | val |
 
         val := aBlock value: each.
-        "Note that there is no way to get the first element that works 
-        for all kinds of Collections.  
-        Must test every one (maxValue is nil for the first element)."
+        "Note that there is no way to get the first element 
+         which works for all kinds of Collections.  
+         Must therefore test every one (minValue is nil for the first element)."
         (minValue == nil or:[val < minValue]) ifTrue: [
            minElement := each.
            minValue := val
@@ -2856,7 +2870,6 @@
      Answer true, if all the elements have been processed,
      false otherwise."
 
-
     self do:[:el |
         (aBlock value:el) ifFalse:[
             ^ false.
@@ -3178,14 +3191,16 @@
 
 keysAndValuesDo:aTwoArgBlock
     "evaluate the argument, aBlock for every element in the collection,
-     passing both index and element as arguments."
+     passing both index and element as arguments.
+     Blocked here - must be redefined in subclasses which have keyed elements"
 
     ^ self errorNotKeyed
 !
 
 keysAndValuesReverseDo:aTwoArgBlock
     "evaluate the argument, aBlock in reverse order for every element in the collection,
-     passing both index and element as arguments."
+     passing both index and element as arguments.
+     Blocked here - must be redefined in subclasses which have keyed elements"
 
     ^ self errorNotKeyed
 
@@ -3193,6 +3208,10 @@
 !
 
 keysAndValuesSelect:selectBlockWith2Args thenCollect:collectBlockWith2Args
+    "first call the selectBlockWith2Args, passsing it each key and element,
+     if that returns true, call the collectBlockWith2Args, also with key and element,
+     and collect the resulting values in an OrderedCollection."
+    
     |collected|
 
     collected := OrderedCollection new.
@@ -3204,7 +3223,9 @@
     ^ collected
 
     "
-     #(10 20 30 40) keysAndValuesSelect:[:idx :val | idx > 2] thenCollect:[:idx :val | idx->val]
+     #(10 20 30 40) 
+        keysAndValuesSelect:[:idx :val | idx > 2] 
+        thenCollect:[:idx :val | idx->val]
     "
 !
 
@@ -3534,7 +3555,7 @@
 !
 
 select:selectBlock thenDo:doBlock
-    "combination of select followed by do
+    "combination of select followed by do.
      The same as if two separate select:+do: messages were sent,
      but avoids the creation of intermediate collections, 
      so this is nicer for big collections."
@@ -3550,6 +3571,25 @@
     "
 !
 
+selectWithIndex:aTwoArgBlock
+    "return a new collection with all elements from the receiver, 
+     for which the argument aBlock evaluates to true.
+     aTwoArgBlock is called with value and index as arguments."
+
+    |newCollection|
+
+    newCollection := self species new.
+    self doWithIndex:[:eachValue :eachKey |
+        (aTwoArgBlock value:eachValue value:eachKey) ifTrue:[newCollection add:eachValue].
+    ].
+    ^ newCollection
+
+    "
+     #(10 20 30 40) selectWithIndex:[:e :i | i odd]   
+     #(10 20 30 40) selectWithIndex:[:e :i | i even]   
+    "
+!
+
 triplesDo:aThreeArgBlock
     "evaluate the argument, aThreeArgBlock for every element in the collection,
      which is supposed to consist of 3-element collections.
@@ -4199,7 +4239,7 @@
     aStream nextPut:$)
 
     "
-     #(1 2 3 'hello' $a $ü) printOn:Transcript
+     #(1 2 3 'hello' $a $ü) printOn:Transcript
      (Array new:100000) printOn:Transcript
      (Array new:100000) printOn:Stdout          
      (Array new:100000) printString size 
@@ -4302,10 +4342,18 @@
 !
 
 isReadOnly
+    "true if this is a readOnly (immutable) collection.
+     Q1: should this be called isImmutable?
+     Q2: who uses this?"
+    
     ^ false
 !
 
 isWritable
+    "true if this is not a readOnly (immutable) collection.
+     Q1: should this be called isMutable?
+     Q2: who uses this?"
+
     ^ self isReadOnly not
 !
 
@@ -5529,7 +5577,7 @@
 includesAll:aCollection
     "return true, if the the receiver includes all elements of
      the argument, aCollection; false if any is missing.
-     Notice: this method has O-square runtime behavior and may be
+     Notice: this method has O² runtime behavior and may be
              slow for big receivers/args. 
              Think about using a Set, or Dictionary."
 
@@ -5548,7 +5596,7 @@
     "return true, if the the receiver includes any elements of
      the argument, aCollection; false if it includes none.
      Notice: 
-        this method has O^2(N) runtime behavior and may be
+        this method has O² runtime behavior and may be
         slow for big receivers/args. 
         Think about using a Set or Dictionary. 
         Some speedup is also possible, by arranging highly
@@ -5612,7 +5660,7 @@
     "return true, if the the receiver includes any elements of
      the argument, aCollection; false if it includes none.
      Use identity compare for comparing.
-     Notice: this method has O^2(N) runtime behavior and may be
+     Notice: this method has O² runtime behavior and may be
              slow for big receivers/args. 
              Think about using a Set or Dictionary. 
              Some speedup is also possible, by arranging highly
--- a/CompiledCode.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/CompiledCode.st	Sat Mar 26 07:56:10 2016 +0000
@@ -506,7 +506,7 @@
 !
 
 mclass
-    "return the class of the receivers home method.
+    "return the class of the receiver's home method.
      Thats the class of the method where the block was compiled."
 
     ^ self homeMethod mclass
--- a/Context.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Context.st	Sat Mar 26 07:56:10 2016 +0000
@@ -756,7 +756,7 @@
 
 searchClass
     "this is the class where the method-lookup started;
-     for normal sends, it is nil (or sometimes the receivers class).
+     for normal sends, it is nil (or sometimes the receiver's class).
      For supersends, its the superclass of the one, in which the
      caller was defined."
 
@@ -1216,19 +1216,19 @@
 
 resume:value
     "resume the receiver - as if it got 'value' from whatever
-     it called. This continues execution in the receivers method
+     it called. This continues execution in the receiver's method
      after the point where it did its last send.
      If the context has already returned - report an error.
 
      NOTICE:
-	 NO unwind actions are performed (see Context>>unwind:).
+         NO unwind actions are performed (see Context>>unwind:).
 
      LIMITATION:
-	 currently a context can only be resumed by
-	 the owning process - not from outside.
-	 Also, the compiler has an option (+optcontext) to create
-	 non-resumable contexts (which are faster).
-	 If such a context is restarted, a runtime error is raised."
+         currently a context can only be resumed by
+         the owning process - not from outside.
+         Also, the compiler has an option (+optcontext) to create
+         non-resumable contexts (which are faster).
+         If such a context is restarted, a runtime error is raised."
 
     |theContext|
 
@@ -1246,43 +1246,43 @@
 
     theContext = __thisContext;
     while (theContext != nil) {
-	sndr = __ContextInstPtr(theContext)->c_sender;
-	if (sndr == self) break;
-	theContext = sndr;
+        sndr = __ContextInstPtr(theContext)->c_sender;
+        if (sndr == self) break;
+        theContext = sndr;
     }
     if (theContext != nil) {
-	if (__isLazy(theContext)) {
-	    __PATCHUPCONTEXT(theContext);
-	}
+        if (__isLazy(theContext)) {
+            __PATCHUPCONTEXT(theContext);
+        }
     }
 #endif
 %}.
 
     theContext isNil ifTrue:[
-	"
-	 tried to resume in context which is already dead
-	 (i.e. the method/block has already executed a return)
-	"
-	^ thisContext invalidReturnOrRestartError:#'resume:' with:value
+        "
+         tried to resume in context which is already dead
+         (i.e. the method/block has already executed a return)
+        "
+        ^ thisContext invalidReturnOrRestartError:#'resume:' with:value
     ].
     ^ theContext return:value
 !
 
 resumeIgnoringErrors:value
     "resume the receiver - as if it got 'value' from whatever
-     it called. This continues execution in the receivers method
+     it called. This continues execution in the receiver's method
      after the point where it did its last send.
      If the context has already returned - simply return.
 
      NOTICE:
-	 NO unwind actions are performed (see Context>>unwind:).
+         NO unwind actions are performed (see Context>>unwind:).
 
      LIMITATION:
-	 currently a context can only be resumed by
-	 the owning process - not from outside.
-	 Also, the compiler has an option (+optcontext) to create
-	 non-resumable contexts (which are faster).
-	 If such a context is restarted, a runtime error is raised."
+         currently a context can only be resumed by
+         the owning process - not from outside.
+         Also, the compiler has an option (+optcontext) to create
+         non-resumable contexts (which are faster).
+         If such a context is restarted, a runtime error is raised."
 
     "
      starting with this context, find the one below
@@ -1298,16 +1298,16 @@
 
     theContext = __thisContext;
     while (theContext != nil) {
-	sndr = __ContextInstPtr(theContext)->c_sender;
-	if (sndr == self) break;
-	theContext = sndr;
+        sndr = __ContextInstPtr(theContext)->c_sender;
+        if (sndr == self) break;
+        theContext = sndr;
     }
     if (theContext != nil) {
-	if (__ContextInstPtr(theContext)->c_sender) {
-	    if (!((INT)(__ContextInstPtr(theContext)->c_flags) & __MASKSMALLINT(__CANNOT_RETURN))) {
-		__RESUMECONTEXT__(theContext, value, 0);
-	    }
-	}
+        if (__ContextInstPtr(theContext)->c_sender) {
+            if (!((INT)(__ContextInstPtr(theContext)->c_flags) & __MASKSMALLINT(__CANNOT_RETURN))) {
+                __RESUMECONTEXT__(theContext, value, 0);
+            }
+        }
     }
 #endif
 %}.
@@ -1317,19 +1317,19 @@
 
 resumeOnErrorProceed:value
     "resume the receiver - as if it got 'value' from whatever
-     it called. This continues execution in the receivers method
+     it called. This continues execution in the receiver's method
      after the point where it did its last send.
      If the context has already returned - simply return.
 
      NOTICE:
-	 NO unwind actions are performed (see Context>>unwind:).
+         NO unwind actions are performed (see Context>>unwind:).
 
      LIMITATION:
-	 currently a context can only be resumed by
-	 the owning process - not from outside.
-	 Also, the compiler has an option (+optcontext) to create
-	 non-resumable contexts (which are faster).
-	 If such a context is restarted, a runtime error is raised."
+         currently a context can only be resumed by
+         the owning process - not from outside.
+         Also, the compiler has an option (+optcontext) to create
+         non-resumable contexts (which are faster).
+         If such a context is restarted, a runtime error is raised."
 
     "
      starting with this context, find the one below
@@ -1345,14 +1345,14 @@
 
     theContext = __thisContext;
     while (theContext != nil) {
-	sndr = __ContextInstPtr(theContext)->c_sender;
-	if (sndr == self) break;
-	theContext = sndr;
+        sndr = __ContextInstPtr(theContext)->c_sender;
+        if (sndr == self) break;
+        theContext = sndr;
     }
     if (theContext != nil) {
-	if (__ContextInstPtr(theContext)->c_sender) {
-	    __RESUMECONTEXT__(theContext, value, 0);
-	}
+        if (__ContextInstPtr(theContext)->c_sender) {
+            __RESUMECONTEXT__(theContext, value, 0);
+        }
     }
 #endif
 %}.
--- a/Date.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Date.st	Sat Mar 26 07:56:10 2016 +0000
@@ -931,6 +931,7 @@
     ^ self newDay:day month:mon year:yr
 ! !
 
+
 !Date class methodsFor:'change & update'!
 
 update:something with:aParameter from:changedObject
@@ -2645,7 +2646,7 @@
 !
 
 asSeconds
-    "return the seconds between 1.jan.1901 and the same time in the receivers 
+    "return the seconds between 1.jan.1901 and the same time in the receiver's 
      day. (i.e. midnight to midnight). The returned number may be negative for dates before 1901.
      This does not include any leapSeconds ... strictly speaking, this is incorrect.
      ST-80 compatibility."
@@ -3302,7 +3303,7 @@
 !
 
 leap
-    "return true, if the receivers year is a leap year"
+    "return true, if the receiver's year is a leap year"
     <resource: #obsolete>
 
     ^ self isLeapYear
--- a/Dictionary.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Dictionary.st	Sat Mar 26 07:56:10 2016 +0000
@@ -292,7 +292,6 @@
     ^ true
 ! !
 
-
 !Dictionary methodsFor:'accessing'!
 
 associationAt:aKey
@@ -321,7 +320,7 @@
 !
 
 associations
-    "return an ordered collection containing the receivers associations."
+    "return an ordered collection containing the receiver's associations."
 
     |coll|
 
@@ -2330,7 +2329,6 @@
     ^ aVisitor visitDictionary:self with:aParameter
 ! !
 
-
 !Dictionary class methodsFor:'documentation'!
 
 version
--- a/ExceptionHandlerSet.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/ExceptionHandlerSet.st	Sat Mar 26 07:56:10 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 IdentityDictionary subclass:#ExceptionHandlerSet
 	instanceVariableNames:''
 	classVariableNames:''
@@ -142,7 +144,7 @@
 
 accepts:anExceptionHandler
     "return true, if the receiver accepts the argument, aSignal.
-     (i.e. if any of the receivers elements is aSignal or a parent of it)."
+     (i.e. if any of the receiver's elements is aSignal or a parent of it)."
 
     self keysDo:[:eachExceptionHandler | 
         (eachExceptionHandler==anExceptionHandler 
@@ -213,7 +215,7 @@
 
 handles:anException
     "return true, if the receiver handles the argument, anException.
-     (i.e. if any of the receivers elements handles anException)."
+     (i.e. if any of the receiver's elements handles anException)."
 
     self keysDo:[:eachExceptionHandler| 
         (eachExceptionHandler handles:anException) ifTrue:[^ true]
@@ -334,7 +336,7 @@
 !ExceptionHandlerSet class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ExceptionHandlerSet.st,v 1.18 2013-04-04 09:37:41 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/Filename.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Filename.st	Sat Mar 26 07:56:10 2016 +0000
@@ -2036,7 +2036,7 @@
 !
 
 components
-    "return the receivers filename components - that is the name of each directory
+    "return the receiver's filename components - that is the name of each directory
      along the pathName (that DOES include the root directory)"
 
     ^ self species components:self name
@@ -2048,7 +2048,7 @@
 !
 
 makeLegalFilename
-    "convert the receivers name to be a legal filename.
+    "convert the receiver's name to be a legal filename.
      This removes/replaces invalid characters and/or compresses
      the name as required by the OS.
      The implementation may change in the future to be more
@@ -2944,7 +2944,7 @@
 !
 
 basicMakeDirectory
-    "create a directory with the receivers name.
+    "create a directory with the receiver's name.
      Return true if successful, false if not."
 
     ^ OperatingSystem createDirectory:(self osNameForDirectory)
@@ -3036,36 +3036,36 @@
 !
 
 createAsEmptyFile
-    "create an empty file with the receivers name.
+    "create an empty file with the receiver's name.
      Raises an exception if not successful
     (either already existing or creation not possible)"
 
     |writeStream|
 
     self exists ifTrue:[
-	OperatingSystem accessDeniedErrorSignal
-	    raiseRequestWith:self
-	    errorString:(' - file exists: ' , self asString).
-	^ self
+        OperatingSystem accessDeniedErrorSignal
+            raiseRequestWith:self
+            errorString:(' - file exists: ' , self asString).
+        ^ self
     ].
 
     FileStream openErrorSignal handle:[:ex|
-	self fileCreationError:self.
-	^ self
+        self fileCreationError:self.
+        ^ self
     ] do:[
-	writeStream := self newReadWriteStream.
+        writeStream := self newReadWriteStream.
     ].
     writeStream close.
 !
 
 createAsSymbolicLinkTo:linkFilenameString
-    "create a directory with the receivers name.
+    "create a directory with the receiver's name.
      Raises an exception if not successful"
 
     OperatingSystem createSymbolicLinkFrom:linkFilenameString to:self pathName.
 
     "
-	'/tmp/link' asFilename makeSymbolicLinkTo:'bla'
+        '/tmp/link' asFilename makeSymbolicLinkTo:'bla'
     "
 !
 
@@ -3076,17 +3076,17 @@
 !
 
 makeDirectory
-    "create a directory with the receivers name.
+    "create a directory with the receiver's name.
      Raises an exception if not successful"
 
     (self basicMakeDirectory) ifFalse:[
-	"/
-	"/ could have existed before ...
-	"/
-	(self exists and:[self isDirectory]) ifFalse:[
-	    self fileCreationError:self.
-	    ^ false
-	]
+        "/
+        "/ could have existed before ...
+        "/
+        (self exists and:[self isDirectory]) ifFalse:[
+            self fileCreationError:self.
+            ^ false
+        ]
     ].
     ^ true
 
@@ -4776,9 +4776,9 @@
      BAD DESIGN: has side effect on the receiver.
      This method has both a return value and a side effect on the receiver:
        it returns a collection of matching filename objects,
-       and changes the receivers filename-string to the longest common
+       and changes the receiver's filename-string to the longest common
        match.
-     If none matches, the returned collection is empty and the recevier is unchanged.
+     If none matches, the returned collection is empty and the receiver is unchanged.
      If there is only one match, the size of the returned collection is exactly 1,
      containing the fully expanded filename and the receivers name is changed to it."
 
@@ -5202,7 +5202,7 @@
 physicalFilename
     "return the fileName representing the physical file as represented by the receiver,
      If the receiver represents a symbolic link, thats the fileName of the
-     final target. Otherwise, its the receivers pathName itself.
+     final target. Otherwise, its the receiver's pathName itself.
      If any file along the symbolic path does not exist (i.e. is a broken link),
      nil is returned."
 
@@ -5210,7 +5210,7 @@
 
     pathOrNil := self physicalPathName.
     pathOrNil isNil ifTrue:[
-	^ nil
+        ^ nil
     ].
     ^ pathOrNil asFilename
 
@@ -5222,7 +5222,7 @@
 physicalPathName
     "return the full pathname of the physical file represented by the receiver,
      If the receiver represents a symbolic link, thats the fileName of the
-     final target. Otherwise, its the receivers pathName itself.
+     final target. Otherwise, its the receiver's pathName itself.
      If any file along the symbolic path does not exist (i.e. is a broken link),
      nil is returned."
 
@@ -5230,30 +5230,30 @@
 
     info := self linkInfo.
     info isNil ifTrue:[
-	" I do not exist"
-	^ nil.
+        " I do not exist"
+        ^ nil.
     ].
     info isSymbolicLink ifFalse:[
-	^ self pathName
+        ^ self pathName
     ].
 
     t := self.
     [
-	path := info path.
-	path isNil ifTrue:[
-	    "/ cannot happen
-	    ^ nil
-	].
-	path asFilename isAbsolute ifTrue:[
-	    t := path asFilename
-	] ifFalse:[
-	    t := (self species named:t directoryName) construct:path.
-	].
-	info := t linkInfo.
-	info isNil ifTrue:[
-	    "t does not exist"
-	     ^ nil
-	].
+        path := info path.
+        path isNil ifTrue:[
+            "/ cannot happen
+            ^ nil
+        ].
+        path asFilename isAbsolute ifTrue:[
+            t := path asFilename
+        ] ifFalse:[
+            t := (self species named:t directoryName) construct:path.
+        ].
+        info := t linkInfo.
+        info isNil ifTrue:[
+            "t does not exist"
+             ^ nil
+        ].
     ] doWhile:[info isSymbolicLink].
 
     ^ t pathName
@@ -5808,7 +5808,7 @@
 !Filename methodsFor:'suffixes'!
 
 addSuffix:aSuffix
-    "return a new filename for the receivers name with a additional suffix.
+    "return a new filename for the receiver's name with a additional suffix.
      The new suffix is simply appended to the name,
      regardless whether there is already an existing suffix.
      See also #withSuffix:"
@@ -5817,13 +5817,13 @@
 
     prefixName := self name.
     aSuffix isEmptyOrNil ifTrue:[
-	^ self species named:prefixName
+        ^ self species named:prefixName
     ].
 
     ^ self species named:
-	(prefixName
-	 , self species suffixSeparator asString
-	 , aSuffix asString)
+        (prefixName
+         , self species suffixSeparator asString
+         , aSuffix asString)
 
     "
      'abc.st' asFilename addSuffix:nil
@@ -5875,7 +5875,7 @@
 !
 
 nameWithoutSuffix
-    "return the receivers name without the suffix.
+    "return the receiver's name without the suffix.
      If the name has no suffix, the original name is returned."
 
     |nm idx idxFromEnd|
@@ -6002,7 +6002,7 @@
 !
 
 withSuffix:aSuffix
-    "return a new filename for the receivers name with a different suffix.
+    "return a new filename for the receiver's name with a different suffix.
      If the name already has a suffix, the new suffix replaces it;
      otherwise, the new suffix is simply appended to the name."
 
@@ -6010,13 +6010,13 @@
 
     prefixName := self nameWithoutSuffix.
     aSuffix isEmptyOrNil ifTrue:[
-	^ self species named:prefixName
+        ^ self species named:prefixName
     ].
 
     ^ self species named:
-	(prefixName
-	 , self class suffixSeparator asString
-	 , aSuffix asString)
+        (prefixName
+         , self class suffixSeparator asString
+         , aSuffix asString)
 
     "
      'abc.st' asFilename withSuffix:nil
@@ -6048,7 +6048,7 @@
 !
 
 withoutSuffix
-    "return a new filename for the receivers name without the suffix.
+    "return a new filename for the receiver's name without the suffix.
      If the name has no suffix, a filename representing the same file as the receiver is returned."
 
     |n|
--- a/Geometric.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Geometric.st	Sat Mar 26 07:56:10 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Object subclass:#Geometric
 	instanceVariableNames:''
 	classVariableNames:'Scale InverseScale'
@@ -458,7 +460,7 @@
 !
 
 outlineIntersects:aRectangle
-    "return true, if the receivers image intersects
+    "return true, if the receiver's image intersects
      aRectangle, when drawn as an outline.
      Here, all we can do is to ask the boundary rectangle;
      subclasses should reimplement better checks."
@@ -469,7 +471,7 @@
 !
 
 regionIntersects:aRectangle
-    "return true, if the receivers image intersects
+    "return true, if the receiver's image intersects
      aRectangle, when drawn as a filled version.
      Here, all we can do is to ask the boundary rectangle;
      subclasses should reimplement better checks."
@@ -652,7 +654,7 @@
 !Geometric class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Geometric.st,v 1.33 2014-07-10 12:23:28 cg Exp $'
+    ^ '$Header$'
 ! !
 
 
--- a/HashStream.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/HashStream.st	Sat Mar 26 07:56:10 2016 +0000
@@ -358,7 +358,7 @@
 !
 
 isReadable
-    "return true, if reading is supported by the recevier.
+    "return true, if reading is supported by the receiver.
      Always return false here"
 
     ^ false
@@ -367,7 +367,7 @@
 !
 
 isWritable
-    "return true, if writing is supported by the recevier.
+    "return true, if writing is supported by the receiver.
      Always return true here"
 
     ^ true
--- a/Integer.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Integer.st	Sat Mar 26 07:56:10 2016 +0000
@@ -754,8 +754,6 @@
     "Modified: / 15.11.1999 / 20:35:20 / cg"
 ! !
 
-
-
 !Integer class methodsFor:'class initialization'!
 
 initialize
@@ -801,7 +799,6 @@
     "Modified: 18.7.1996 / 12:26:38 / cg"
 ! !
 
-
 !Integer class methodsFor:'prime numbers'!
 
 flushPrimeCache
@@ -1172,12 +1169,11 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for Integer here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == Integer
 ! !
 
-
 !Integer methodsFor:'Compatibility-Dolphin'!
 
 & aNumber
@@ -1443,7 +1439,6 @@
 ! !
 
 
-
 !Integer methodsFor:'bcd conversion'!
 
 decodeFromBCD
@@ -4857,7 +4852,6 @@
     "Created: / 09-01-2012 / 17:18:06 / cg"
 ! !
 
-
 !Integer methodsFor:'special modulo arithmetic'!
 
 add_32:anInteger
--- a/Interval.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Interval.st	Sat Mar 26 07:56:10 2016 +0000
@@ -260,7 +260,7 @@
 !Interval methodsFor:'converting-reindexed'!
 
 from:startIndex
-    "return a new collection representing the receivers elements starting at startIndex."
+    "return a new collection representing the receiver's elements starting at startIndex."
 
     step == 1 ifTrue:[
         ^ start+startIndex-1 to:stop
@@ -278,7 +278,7 @@
 !
 
 to:endIndex
-    "return a new collection representing the receivers elements upTo and including endIndex."
+    "return a new collection representing the receiver's elements upTo and including endIndex."
 
     ^ start to:(endIndex min:stop) by:step
 
--- a/KeyedCollection.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/KeyedCollection.st	Sat Mar 26 07:56:10 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Collection subclass:#KeyedCollection
 	instanceVariableNames:''
 	classVariableNames:''
@@ -60,7 +62,7 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for KeyedCollection here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == KeyedCollection
 ! !
@@ -199,10 +201,10 @@
 !KeyedCollection class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/KeyedCollection.st,v 1.9 2014-11-26 08:39:20 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/KeyedCollection.st,v 1.9 2014-11-26 08:39:20 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/LibraryDefinition.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/LibraryDefinition.st	Sat Mar 26 07:56:10 2016 +0000
@@ -674,6 +674,10 @@
     "
 !
 
+isAbstract
+    ^ self == LibraryDefinition
+!
+
 projectType
     ^ LibraryType
 !
@@ -727,10 +731,6 @@
 
 !LibraryDefinition class methodsFor:'testing'!
 
-isAbstract
-    ^ self == LibraryDefinition
-!
-
 isLibraryDefinition
     ^ self isAbstract not
 
--- a/LookupKey.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/LookupKey.st	Sat Mar 26 07:56:10 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Magnitude subclass:#LookupKey
 	instanceVariableNames:'key'
 	classVariableNames:''
@@ -74,22 +76,22 @@
 !LookupKey methodsFor:'comparing'!
 
 < aKey
-    "return true, if the receivers KEY is less 
-     than the arguments key. The argument must be a kind of lookupKey"
+    "return true, if the receiver's Key is less than the argument's key. 
+     The argument must be a kind of lookupKey"
 
     ^ key < aKey key
 !
 
 = aLookupKey
-    "return true if the receivers key equals the arguments key.
+    "return true if the receiver's key equals the argument's key.
      The argument must be a kind of lookupKey."
 
     ^ (self species == aLookupKey species) and:[key = aLookupKey key]
 !
 
 > aKey
-    "return true, if the receivers KEY is greater 
-     than the arguments key. The argument must be a kind of lookupKey"
+    "return true, if the receiver's Key is greater than the argument's key. 
+     The argument must be a kind of lookupKey"
 
     ^ key > aKey key
 !
@@ -131,10 +133,9 @@
     key printOn:aStream.
 ! !
 
-
 !LookupKey class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/LookupKey.st,v 1.12 2014-07-10 12:24:01 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/Magnitude.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Magnitude.st	Sat Mar 26 07:56:10 2016 +0000
@@ -51,7 +51,7 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for Magnitude here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == Magnitude
 ! !
--- a/Method.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Method.st	Sat Mar 26 07:56:10 2016 +0000
@@ -1411,7 +1411,7 @@
 
 asExecutableMethod
     "if the receiver has neither bytecodes nor machinecode, create & return a
-     method having semantics as the receivers source. This may be machine code,
+     method having semantics as the receiver's source. This may be machine code,
      if the system supports dynamic loading of object code and the source includes
      primitive code. However, bytecode is preferred, since it compiles faster.
      Otherwise, return the receiver. The new method is not installed in
@@ -1421,23 +1421,23 @@
     |temporaryMethod sourceString|
 
     byteCode notNil ifTrue:[
-	"
-	 is already a bytecoded method
-	"
-	^ self
+        "
+         is already a bytecoded method
+        "
+        ^ self
     ].
 
     sourceString := self source.
     sourceString isNil ifTrue:[
-	'Method [warning]: cannot generate bytecode (no source for compilation)' errorPrintCR.
-	^ nil
+        'Method [warning]: cannot generate bytecode (no source for compilation)' errorPrintCR.
+        ^ nil
     ].
 
     temporaryMethod := self asExecutableMethodWithSource:sourceString.
 
     (temporaryMethod isNil or:[temporaryMethod == #Error]) ifTrue:[
-	'Method [warning]: cannot generate bytecode (contains primitive code or error)' errorPrintCR.
-	^ nil.
+        'Method [warning]: cannot generate bytecode (contains primitive code or error)' errorPrintCR.
+        ^ nil.
     ].
     "/
     "/ try to save a bit of memory, by sharing the source (whatever it is)
@@ -2985,7 +2985,7 @@
 
 modificationTime
     "try to extract the modificationTime as a timeStamp from
-     the receivers source. If there is no source or no history line,
+     the receiver's source. If there is no source or no history line,
      we do not know the modification time, and nil is returned."
 
     |s list histLine|
@@ -2998,8 +2998,8 @@
     list isEmptyOrNil ifTrue:[^ nil].
     histLine := list last.
     ^ Timestamp
-	fromDate:histLine date
-	andTime:histLine time
+        fromDate:histLine date
+        andTime:histLine time
 
     "
      (Method compiledMethodAt:#modificationTime) modificationTime
@@ -3176,7 +3176,7 @@
 !
 
 previousVersion
-    "return the receivers previous version's source code"
+    "return the receiver's previous version's source code"
 
     |previous|
 
@@ -3227,7 +3227,7 @@
 !
 
 previousVersionCode
-    "return the receivers previous versions source code"
+    "return the receiver's previous version's source code"
 
     |previous|
 
--- a/Number.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Number.st	Sat Mar 26 07:56:10 2016 +0000
@@ -711,7 +711,6 @@
     "
 ! !
 
-
 !Number class methodsFor:'private'!
 
 readMantissaAndScaleFrom:aStream radix:radix
@@ -781,12 +780,11 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for Number here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == Number
 ! !
 
-
 !Number methodsFor:'Compatibility-Squeak'!
 
 asSmallAngleDegrees
@@ -2668,7 +2666,6 @@
     "Modified: / 5.11.2001 / 17:54:22 / cg"
 ! !
 
-
 !Number class methodsFor:'documentation'!
 
 version
--- a/Object.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Object.st	Sat Mar 26 07:56:10 2016 +0000
@@ -499,7 +499,7 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for Object here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == Object
 !
@@ -1402,7 +1402,7 @@
     "return the byte at index.
      This is only allowed for non-pointer indexed objects
      (i.e. byteArrays, wordArrays, floatArrays etc.).
-     The receivers indexed instvars are treated as an uninterpreted
+     The receiver's indexed instvars are treated as an uninterpreted
      collection of bytes.
      Only useful with binary storage."
 
@@ -1414,56 +1414,56 @@
     REGISTER OBJ cls;
 
     if (__isSmallInteger(index)) {
-	slf = self;
-	if (__isNonNilObject(slf)) {
-	    unsigned char *pFirst;
-	    int nIndex;
-
-	    cls = __qClass(slf);
-
-	    pFirst = __byteArrayVal(slf);
-	    pFirst += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-	    nIndex = __byteArraySize(slf);
-	    indx = __intVal(index) - 1;
-
-	    switch ((INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
-		case __MASKSMALLINT(DOUBLEARRAY):
+        slf = self;
+        if (__isNonNilObject(slf)) {
+            unsigned char *pFirst;
+            int nIndex;
+
+            cls = __qClass(slf);
+
+            pFirst = __byteArrayVal(slf);
+            pFirst += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+            nIndex = __byteArraySize(slf);
+            indx = __intVal(index) - 1;
+
+            switch ((INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
+                case __MASKSMALLINT(DOUBLEARRAY):
 #ifdef __NEED_DOUBLE_ALIGN
-		    if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
-			int delta = __DOUBLE_ALIGN - ((INT)pFirst & (__DOUBLE_ALIGN-1));
-
-			pFirst += delta;
-			nIndex -= delta;
-		    }
+                    if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
+                        int delta = __DOUBLE_ALIGN - ((INT)pFirst & (__DOUBLE_ALIGN-1));
+
+                        pFirst += delta;
+                        nIndex -= delta;
+                    }
 #endif
-		    /* fall into */
-		case __MASKSMALLINT(BYTEARRAY):
-		case __MASKSMALLINT(WORDARRAY):
-		case __MASKSMALLINT(LONGARRAY):
-		case __MASKSMALLINT(SWORDARRAY):
-		case __MASKSMALLINT(SLONGARRAY):
-		case __MASKSMALLINT(FLOATARRAY):
-		    if ((unsigned)indx < (unsigned)nIndex) {
-			RETURN ( __mkSmallInteger( (INT)(pFirst[indx])) );
-		    }
-		    break;
-
-		case __MASKSMALLINT(LONGLONGARRAY):
-		case __MASKSMALLINT(SLONGLONGARRAY):
+                    /* fall into */
+                case __MASKSMALLINT(BYTEARRAY):
+                case __MASKSMALLINT(WORDARRAY):
+                case __MASKSMALLINT(LONGARRAY):
+                case __MASKSMALLINT(SWORDARRAY):
+                case __MASKSMALLINT(SLONGARRAY):
+                case __MASKSMALLINT(FLOATARRAY):
+                    if ((unsigned)indx < (unsigned)nIndex) {
+                        RETURN ( __mkSmallInteger( (INT)(pFirst[indx])) );
+                    }
+                    break;
+
+                case __MASKSMALLINT(LONGLONGARRAY):
+                case __MASKSMALLINT(SLONGLONGARRAY):
 #ifdef __NEED_LONGLONG_ALIGN
-		    if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
-			int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
-
-			pFirst += delta;
-			nIndex -= delta;
-		    }
+                    if ((INT)pFirst & (__LONGLONG_ALIGN-1)) {
+                        int delta = __LONGLONG_ALIGN - ((INT)pFirst & (__LONGLONG_ALIGN-1));
+
+                        pFirst += delta;
+                        nIndex -= delta;
+                    }
 #endif
-		    if ((unsigned)indx < (unsigned)nIndex) {
-			RETURN ( __mkSmallInteger( (INT)(pFirst[indx])) );
-		    }
-		    break;
-	    }
-	}
+                    if ((unsigned)indx < (unsigned)nIndex) {
+                        RETURN ( __mkSmallInteger( (INT)(pFirst[indx])) );
+                    }
+                    break;
+            }
+        }
     }
 %}.
     "/ index not integer or index out of range
@@ -1484,7 +1484,7 @@
     "set the byte at index.
      This is only allowed for non-pointer indexed objects
      (i.e. byteArrays, wordArrays, floatArrays etc.).
-     The receivers indexed instvars are treated as an uninterpreted
+     The receiver's indexed instvars are treated as an uninterpreted
      collection of bytes.
      Only useful with binary storage."
 
@@ -1496,33 +1496,33 @@
     REGISTER OBJ cls;
 
     if (__bothSmallInteger(index, byteValue)) {
-	val = __intVal(byteValue);
-	if ((unsigned)(val) <= 0xFF /* i.e. (val >= 0) && (val <= 255) */) {
-	    slf = self;
-	    if (__isNonNilObject(slf)) {
-		cls = __qClass(slf);
-
-		indx = __intVal(index) - 1;
-		switch ((INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
-		    case __MASKSMALLINT(BYTEARRAY):
-		    case __MASKSMALLINT(WORDARRAY):
-		    case __MASKSMALLINT(LONGARRAY):
-		    case __MASKSMALLINT(SWORDARRAY):
-		    case __MASKSMALLINT(SLONGARRAY):
-		    case __MASKSMALLINT(LONGLONGARRAY):
-		    case __MASKSMALLINT(SLONGLONGARRAY):
-		    case __MASKSMALLINT(FLOATARRAY):
-		    case __MASKSMALLINT(DOUBLEARRAY):
-			indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-			nIndex = __byteArraySize(slf);
-			if ((unsigned)indx < (unsigned)nIndex) {
-			    __ByteArrayInstPtr(slf)->ba_element[indx] = val;
-			    RETURN ( byteValue );
-			}
-			break;
-		}
-	    }
-	}
+        val = __intVal(byteValue);
+        if ((unsigned)(val) <= 0xFF /* i.e. (val >= 0) && (val <= 255) */) {
+            slf = self;
+            if (__isNonNilObject(slf)) {
+                cls = __qClass(slf);
+
+                indx = __intVal(index) - 1;
+                switch ((INT)(__ClassInstPtr(cls)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
+                    case __MASKSMALLINT(BYTEARRAY):
+                    case __MASKSMALLINT(WORDARRAY):
+                    case __MASKSMALLINT(LONGARRAY):
+                    case __MASKSMALLINT(SWORDARRAY):
+                    case __MASKSMALLINT(SLONGARRAY):
+                    case __MASKSMALLINT(LONGLONGARRAY):
+                    case __MASKSMALLINT(SLONGLONGARRAY):
+                    case __MASKSMALLINT(FLOATARRAY):
+                    case __MASKSMALLINT(DOUBLEARRAY):
+                        indx += __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+                        nIndex = __byteArraySize(slf);
+                        if ((unsigned)indx < (unsigned)nIndex) {
+                            __ByteArrayInstPtr(slf)->ba_element[indx] = val;
+                            RETURN ( byteValue );
+                        }
+                        break;
+                }
+            }
+        }
     }
 %}.
     "/ index not integer or index out of range
@@ -2610,7 +2610,7 @@
 deepCopy
     "return a copy of the object with all subobjects also copied.
      This method DOES handle cycles/self-refs and preserves object identity;
-     however the receivers class is not copied (to avoid the 'total' copy).
+     however the receiver's class is not copied (to avoid the 'total' copy).
 
      This deepCopy is a bit slower than the old (unsecure) one, since it
      keeps track of already copied objects. If you are sure, that your
@@ -3833,7 +3833,7 @@
 displayOn:aGc x:x y:y opaque:opaque
     "display the receiver in a graphicsContext - this method allows
      for any object to be displayed in a ListView - for example.
-     The fallBack here shows the receivers displayString.
+     The fallBack here shows the receiver's displayString.
      Notice, that the string is displayed on the baseLine;
      ask using #ascentOn: if required"
 
@@ -3842,9 +3842,9 @@
     s := self isString ifTrue:[self] ifFalse:[self displayString].
     yBaseline := y "+ aGc font ascent".
     opaque ifTrue:[
-	aGc displayOpaqueString:s x:x y:yBaseline.
+        aGc displayOpaqueString:s x:x y:yBaseline.
     ] ifFalse:[
-	aGc displayString:s x:x y:yBaseline.
+        aGc displayString:s x:x y:yBaseline.
     ].
 
     "Modified: 29.5.1996 / 16:29:38 / cg"
@@ -7078,7 +7078,7 @@
 !Object methodsFor:'printing & storing'!
 
 basicPrintOn:aStream
-    "append the receivers className with an articel to the argument, aStream"
+    "append the receiver's className with an article to the argument, aStream"
 
     aStream nextPutAll:self classNameWithArticle
 !
@@ -7295,7 +7295,7 @@
     "append a user printed representation of the receiver to aStream.
      The format is suitable for a human - not meant to be read back.
 
-     The default here is to output the receivers class name.
+     The default here is to output the receiver's class name.
      BUT: this method is heavily redefined for objects which
      can print prettier."
 
@@ -7780,7 +7780,7 @@
 !Object methodsFor:'queries'!
 
 basicSize
-    "return the number of the receivers indexed instance variables,
+    "return the number of the receiver's indexed instance variables,
      0 if it has none.
 
      This method should NOT be redefined in any subclass (except with great care, for tuning)"
@@ -7803,43 +7803,43 @@
     nInstBytes = OHDR_SIZE + __OBJS2BYTES__( __intVal(__ClassInstPtr(myClass)->c_ninstvars) );
 
     switch ((INT)(__ClassInstPtr(myClass)->c_flags) & __MASKSMALLINT(ARRAYMASK)) {
-	case __MASKSMALLINT(POINTERARRAY):
-	case __MASKSMALLINT(WKPOINTERARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(__BYTES2OBJS__(nbytes)) );
-
-	case __MASKSMALLINT(BYTEARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes / sizeof(char)) );
-
-	case __MASKSMALLINT(FLOATARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes / sizeof(float)) );
-
-	case __MASKSMALLINT(DOUBLEARRAY):
+        case __MASKSMALLINT(POINTERARRAY):
+        case __MASKSMALLINT(WKPOINTERARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(__BYTES2OBJS__(nbytes)) );
+
+        case __MASKSMALLINT(BYTEARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes / sizeof(char)) );
+
+        case __MASKSMALLINT(FLOATARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes / sizeof(float)) );
+
+        case __MASKSMALLINT(DOUBLEARRAY):
 # ifdef __NEED_DOUBLE_ALIGN
-	    nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
+            nInstBytes = (nInstBytes-1+__DOUBLE_ALIGN) &~ (__DOUBLE_ALIGN-1);
 # endif
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes / sizeof(double)) );
-
-	case __MASKSMALLINT(WORDARRAY):
-	case __MASKSMALLINT(SWORDARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes>>1) ); /* notice the hardcoded 2 here - not sizeof(short) */
-
-	case __MASKSMALLINT(LONGARRAY):
-	case __MASKSMALLINT(SLONGARRAY):
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes>>2) ); /* notice the hardcoded 4 here - not sizeof(int) */
-
-	case __MASKSMALLINT(LONGLONGARRAY):
-	case __MASKSMALLINT(SLONGLONGARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes / sizeof(double)) );
+
+        case __MASKSMALLINT(WORDARRAY):
+        case __MASKSMALLINT(SWORDARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes>>1) ); /* notice the hardcoded 2 here - not sizeof(short) */
+
+        case __MASKSMALLINT(LONGARRAY):
+        case __MASKSMALLINT(SLONGARRAY):
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes>>2) ); /* notice the hardcoded 4 here - not sizeof(int) */
+
+        case __MASKSMALLINT(LONGLONGARRAY):
+        case __MASKSMALLINT(SLONGLONGARRAY):
 # ifdef __NEED_LONGLONG_ALIGN
-	    nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
+            nInstBytes = (nInstBytes-1+__LONGLONG_ALIGN) &~ (__LONGLONG_ALIGN-1);
 # endif
-	    nbytes -= nInstBytes;
-	    RETURN ( __mkSmallInteger(nbytes>>3) ); /* notice the hardcoded 8 here - not sizeof(long long) */
+            nbytes -= nInstBytes;
+            RETURN ( __mkSmallInteger(nbytes>>3) ); /* notice the hardcoded 8 here - not sizeof(long long) */
     }
 #endif /* not __SCHTEAM__ */
 %}.
@@ -7847,7 +7847,7 @@
 !
 
 byteSize
-    "return the number of bytes in the receivers indexed instance variables,
+    "return the number of bytes in the receiver's indexed instance variables,
      0 if it has none. This only returns non-zero for non-pointer indexed
      instvars i.e. byteArrays, wordArrays etc.
      Notice: for Strings the returned size may look strange.
@@ -7857,36 +7857,36 @@
 
     myClass := self class.
     myClass isVariable ifTrue:[
-	myClass isPointers ifFalse:[
-	    myClass isBytes ifTrue:[
-		^ self basicSize.
-	    ].
-	    myClass isWords ifTrue:[
-		^ self basicSize * 2.
-	    ].
-	    myClass isSignedWords ifTrue:[
-		^ self basicSize * 2.
-	    ].
-	    myClass isLongs ifTrue:[
-		^ self basicSize * 4.
-	    ].
-	    myClass isSignedLongs ifTrue:[
-		^ self basicSize * 4.
-	    ].
-	    myClass isLongLongs ifTrue:[
-		^ self basicSize * 8.
-	    ].
-	    myClass isSignedLongLongs ifTrue:[
-		^ self basicSize * 8.
-	    ].
-	    myClass isFloats ifTrue:[
-		^ self basicSize * (ExternalBytes sizeofFloat)
-	    ].
-	    myClass isDoubles ifTrue:[
-		^ self basicSize * (ExternalBytes sizeofDouble)
-	    ].
-	    self error:'unknown variable size class species'.
-	]
+        myClass isPointers ifFalse:[
+            myClass isBytes ifTrue:[
+                ^ self basicSize.
+            ].
+            myClass isWords ifTrue:[
+                ^ self basicSize * 2.
+            ].
+            myClass isSignedWords ifTrue:[
+                ^ self basicSize * 2.
+            ].
+            myClass isLongs ifTrue:[
+                ^ self basicSize * 4.
+            ].
+            myClass isSignedLongs ifTrue:[
+                ^ self basicSize * 4.
+            ].
+            myClass isLongLongs ifTrue:[
+                ^ self basicSize * 8.
+            ].
+            myClass isSignedLongLongs ifTrue:[
+                ^ self basicSize * 8.
+            ].
+            myClass isFloats ifTrue:[
+                ^ self basicSize * (ExternalBytes sizeofFloat)
+            ].
+            myClass isDoubles ifTrue:[
+                ^ self basicSize * (ExternalBytes sizeofDouble)
+            ].
+            self error:'unknown variable size class species'.
+        ]
     ].
     ^ 0
 
@@ -7916,7 +7916,7 @@
 respondsTo:aSelector
     "return true, if the receiver implements a method with selector equal
      to aSelector; i.e. if there is a method for aSelector in either the
-     receivers class or one of its superclasses.
+     receiver's class or one of its superclasses.
 
      Notice, that this does not imply, that such a message can be sent without
      an error being raised. For example, an implementation could send
@@ -7931,7 +7931,7 @@
 %{  /* NOCONTEXT */
 
     if (__lookup(__Class(self), aSelector) == nil) {
-	RETURN ( false );
+        RETURN ( false );
     }
     RETURN ( true );
 %}
@@ -7952,14 +7952,14 @@
 !
 
 size
-    "return the number of the receivers indexed instance variables;
+    "return the number of the receiver's indexed instance variables;
      this method may be redefined in subclasses"
 
     ^ self basicSize
 !
 
 species
-    "return a class which is similar to (or the same as) the receivers class.
+    "return a class which is similar to (or the same as) the receiver's class.
      This is used to create an appropriate object when creating derived
      copies in the collection classes (sometimes redefined)."
 
@@ -8765,7 +8765,7 @@
 
 changeClassTo:otherClass
     "changes the class of the receiver to the argument, otherClass.
-     This is only allowed (possible), if the receivers class and the argument
+     This is only allowed (possible), if the receiver's class and the argument
      have the same structure (i.e. number of named instance variables and
      type of indexed instance variables).
      If the structures do not match, or any of the original class or new class
@@ -8779,86 +8779,86 @@
 %{
 #ifdef __SCHTEAM__
     ok = (self.isSTInstance() && otherClass.isSTInstance())
-	    ? STObject.True : STObject.False;
+            ? STObject.True : STObject.False;
 #else
     {
-	OBJ other = otherClass;
-
-	if (__isNonNilObject(self)
-	 && __isNonNilObject(other)
-	 && (other != UndefinedObject)
-	 && (other != SmallInteger)) {
-	    ok = true;
-	} else {
-	    ok = false;
-	}
+        OBJ other = otherClass;
+
+        if (__isNonNilObject(self)
+         && __isNonNilObject(other)
+         && (other != UndefinedObject)
+         && (other != SmallInteger)) {
+            ok = true;
+        } else {
+            ok = false;
+        }
     }
 #endif /* not SCHTEAM */
 %}.
     ok == true ifTrue:[
-	ok := false.
-	myClass := self class.
-	myClass == otherClass ifTrue:[
-	    "nothing to change"
-	    ^ self.
-	].
-	myClass flags == otherClass flags ifTrue:[
-	    myClass instSize == otherClass instSize ifTrue:[
-		"same instance layout and types: its ok to do it"
-		ok := true.
-	    ] ifFalse:[
-		myClass isPointers ifTrue:[
-		    myClass isVariable ifTrue:[
-			ok := true
-		    ]
-		]
-	    ]
-	] ifFalse:[
-	    myClass isPointers ifTrue:[
-		"if newClass is a variable class, with instSize <= my instsize,
-		 we can do it (effectively mapping additional instvars into the
-		 variable part) - usefulness is questionable, though"
-
-		otherClass isPointers ifTrue:[
-		    otherClass isVariable ifTrue:[
-			otherClass instSize <= (myClass instSize + self basicSize)
-			ifTrue:[
-			    ok := true
-			]
-		    ] ifFalse:[
-			otherClass instSize == (myClass instSize + self basicSize)
-			ifTrue:[
-			    ok := true
-			]
-		    ]
-		] ifFalse:[
-		    "it does not make sense to convert pointers to bytes ..."
-		]
-	    ] ifFalse:[
-		"does it make sense, to convert bits ?"
-		"could allow byteArray->wordArray->longArray->floatArray->doubleArray here ..."
-		(myClass isBitsExtended and:[otherClass isBitsExtended]) ifTrue:[
-		    ok := true
-		]
-	    ]
-	]
+        ok := false.
+        myClass := self class.
+        myClass == otherClass ifTrue:[
+            "nothing to change"
+            ^ self.
+        ].
+        myClass flags == otherClass flags ifTrue:[
+            myClass instSize == otherClass instSize ifTrue:[
+                "same instance layout and types: its ok to do it"
+                ok := true.
+            ] ifFalse:[
+                myClass isPointers ifTrue:[
+                    myClass isVariable ifTrue:[
+                        ok := true
+                    ]
+                ]
+            ]
+        ] ifFalse:[
+            myClass isPointers ifTrue:[
+                "if newClass is a variable class, with instSize <= my instsize,
+                 we can do it (effectively mapping additional instvars into the
+                 variable part) - usefulness is questionable, though"
+
+                otherClass isPointers ifTrue:[
+                    otherClass isVariable ifTrue:[
+                        otherClass instSize <= (myClass instSize + self basicSize)
+                        ifTrue:[
+                            ok := true
+                        ]
+                    ] ifFalse:[
+                        otherClass instSize == (myClass instSize + self basicSize)
+                        ifTrue:[
+                            ok := true
+                        ]
+                    ]
+                ] ifFalse:[
+                    "it does not make sense to convert pointers to bytes ..."
+                ]
+            ] ifFalse:[
+                "does it make sense, to convert bits ?"
+                "could allow byteArray->wordArray->longArray->floatArray->doubleArray here ..."
+                (myClass isBitsExtended and:[otherClass isBitsExtended]) ifTrue:[
+                    ok := true
+                ]
+            ]
+        ]
     ].
     ok == true ifTrue:[
-	"now, change the receiver's class ..."
+        "now, change the receiver's class ..."
 %{
 #ifdef __SCHTEAM__
-	((STInstance)self).clazz = (STClass)otherClass;
-	return __c__._RETURN(self);
+        ((STInstance)self).clazz = (STClass)otherClass;
+        return __c__._RETURN(self);
 #else
-	{
-	    OBJ me = self;
-
-	    // gcc4.4 does not like this:
-	    // __qClass(me) = otherClass;
-	    __objPtr(me)->o_class = (CLASS_OBJ)otherClass;
-	    __STORE(me, otherClass);
-	    RETURN (me);
-	}
+        {
+            OBJ me = self;
+
+            // gcc4.4 does not like this:
+            // __qClass(me) = otherClass;
+            __objPtr(me)->o_class = (CLASS_OBJ)otherClass;
+            __STORE(me, otherClass);
+            RETURN (me);
+        }
 #endif /* not SCHTEAM */
 %}.
     ].
@@ -8874,7 +8874,7 @@
 
 changeClassToThatOf:anObject
     "changes the class of the receiver to that of the argument, anObject.
-     This is only allowed (possible), if the receivers class and the arguments
+     This is only allowed (possible), if the receiver's class and the arguments
      class have the same structure (i.e. number of named instance variables and
      type of indexed instance variables). If the structures do not match, or any
      of the objects is nil or a Smallinteger, a primitive error is triggered."
@@ -8963,30 +8963,30 @@
       if the receiver is nil, return the defaultValue;
       otherwise, return the receiver.
       This method is only redefined in UndefinedObject - therefore,
-      the recevier is retuned here.
+      the receiver is retuned here.
 
       Thus, if foo and bar are simple variables or constants,
-	  foo ? bar
+          foo ? bar
       is the same as:
-	  (foo isNil ifTrue:[bar] ifFalse:[foo])
+          (foo isNil ifTrue:[bar] ifFalse:[foo])
 
       if they are message sends, the equivalent code is:
-	  [
-	      |t1 t2|
-
-	      t1 := foo.
-	      t2 := bar.
-	      t1 isNil ifTrue:[t2] ifFalse:[t1]
-	  ] value
+          [
+              |t1 t2|
+
+              t1 := foo.
+              t2 := bar.
+              t1 isNil ifTrue:[t2] ifFalse:[t1]
+          ] value
 
       Can be used to provide defaultValues to variables,
       as in:
-	  foo := arg ? #defaultValue
+          foo := arg ? #defaultValue
 
       Note: this method should never be redefined in classes other than UndefinedObject.
       Notice:
-	 This method is open coded (inlined) by the compiler(s)
-	 - redefining it may not work as expected."
+         This method is open coded (inlined) by the compiler(s)
+         - redefining it may not work as expected."
 
     ^ self
 
--- a/Point.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Point.st	Sat Mar 26 07:56:10 2016 +0000
@@ -589,7 +589,7 @@
 
 scaleBy:aScale
     "scale the receiver, by replacing coordinates by the product
-     of the receivers coordinates and the scale (a Point or Number).
+     of the receiver's coordinates and the scale (a Point or Number).
      This is destructive (modifies the receiver, not a copy) and 
      should only be used if you know, that you are the exclusive owner 
      of the receiver."
@@ -597,14 +597,14 @@
     |scalePoint|
 
     (aScale isMemberOf:Point) ifTrue:[  "type hint to stc"  
-	x := x * aScale x.
-	y := y * aScale y.
-	^ self
+        x := x * aScale x.
+        y := y * aScale y.
+        ^ self
     ].
     aScale isNumber ifTrue:[
-	x := x * aScale.
-	y := y * aScale.
-	^ self
+        x := x * aScale.
+        y := y * aScale.
+        ^ self
     ].
 
     "this is the general (& clean) code ..."
@@ -616,7 +616,7 @@
 
 translateBy:anOffset
     "translate the receiver, by replacing coordinates by the sum
-     of the receivers coordinated and the scale (a Point or Number).
+     of the receiver's coordinated and the scale (a Point or Number).
      This is destructive (modifies the receiver, not a copy) and 
      should only be used if you know, that you are the exclusive owner 
      of the receiver."
@@ -624,14 +624,14 @@
     |offsetPoint|
 
     (anOffset isMemberOf:Point) ifTrue:[ "type hint to stc"   
-	x := x + anOffset x.
-	y := y + anOffset y.
-	^ self
+        x := x + anOffset x.
+        y := y + anOffset y.
+        ^ self
     ].
     anOffset isNumber ifTrue:[
-	x := x + anOffset.
-	y := y + anOffset.
-	^ self
+        x := x + anOffset.
+        y := y + anOffset.
+        ^ self
     ].
 
     "this is the general (& clean) code ..."
--- a/Process.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Process.st	Sat Mar 26 07:56:10 2016 +0000
@@ -616,7 +616,7 @@
 !
 
 priority
-    "return the receivers priority"
+    "return the receiver's priority"
 
     ^ prio
 !
@@ -1287,7 +1287,7 @@
 !
 
 setStartBlock:aBlock
-    "set the receivers startup block"
+    "set the receiver's startup block"
 
     startBlock := aBlock
 !
@@ -1814,34 +1814,34 @@
 
     suspendSemaphore notNil ifTrue:[suspendSemaphore signalForAll].
     suspendActions notNil ifTrue:[
-	|savedState|
-
-	savedState := state.
-	state := #aboutToSuspend.
-	suspendActions do:[:action | action value].
-	state ~~ #aboutToSuspend ifTrue:[
-	    "/ mhmh - one of the suspendActions lead to making me active again;
-	    "/ bail out.
-	    "/ This fixes the Semaphore was signalled, but process did not run error,
-	    "/ which can happen when a process with a suspend action goes into a readWait,
-	    "/ and the suspend action does a thread switch, and the readWait semaphore gets
-	    "/ signalled before we come back here. Then the semaphore wakeup will have already
-	    "/ place me back into the run state, so I should not go into a suspend below.
-	    ^ self.
-	].
-	state := savedState.
+        |savedState|
+
+        savedState := state.
+        state := #aboutToSuspend.
+        suspendActions do:[:action | action value].
+        state ~~ #aboutToSuspend ifTrue:[
+            "/ mhmh - one of the suspendActions lead to making me active again;
+            "/ bail out.
+            "/ This fixes the Semaphore was signalled, but process did not run error,
+            "/ which can happen when a process with a suspend action goes into a readWait,
+            "/ and the suspend action does a thread switch, and the readWait semaphore gets
+            "/ signalled before we come back here. Then the semaphore wakeup will have already
+            "/ place me back into the run state, so I should not go into a suspend below.
+            ^ self.
+        ].
+        state := savedState.
     ].
 
     "
      this is a bit of a kludge: allow someone else to
      set the state to something like #ioWait etc.
-     In this case, do not set the receivers state to #suspend.
+     In this case, do not set the receiver's state to #suspend.
      (All of this to enhance the output of the process monitor ...)
     "
     (state == #active
     or:[state == #run
     or:[aStateSymbol == #stopped]]) ifTrue:[
-	state := aStateSymbol.
+        state := aStateSymbol.
     ].
     Processor suspend:self
 !
@@ -1908,31 +1908,31 @@
 !
 
 terminateAllGUISubprocesses
-    "terminate all the receivers gui subprocesses and their children as well
+    "terminate all the receiver's gui subprocesses and their children as well
      (i.e. all processes which are offsprings of the receiver, except for
       the receiver itself)."
 
     id isNil ifTrue:[
-	"/ problem:
-	"/ if receiver is already dead, its id is nil.
-	"/ children are found by looking for processes with a parentID identical to
-	"/ mine - ifNil, system processes are found, which is probably not what you
-	"/ want ...
-	"/ FIX: remember the id (or dont nil it when terminating)
-	"/ requires VM changes.
-	ProcessorScheduler invalidProcessSignal
-	    raiseRequestWith:self
-	    errorString:'process is already dead - cannot determine child processes'.
-	^ self
+        "/ problem:
+        "/ if receiver is already dead, its id is nil.
+        "/ children are found by looking for processes with a parentID identical to
+        "/ mine - ifNil, system processes are found, which is probably not what you
+        "/ want ...
+        "/ FIX: remember the id (or dont nil it when terminating)
+        "/ requires VM changes.
+        ProcessorScheduler invalidProcessSignal
+            raiseRequestWith:self
+            errorString:'process is already dead - cannot determine child processes'.
+        ^ self
     ].
     ProcessorScheduler knownProcesses do:[:aProcess |
-	aProcess ~~ self ifTrue:[
-	    aProcess creatorId == id ifTrue:[
-		aProcess isGUIProcess ifTrue:[
-		    aProcess terminateWithAllGUISubprocesses
-		]
-	    ]
-	]
+        aProcess ~~ self ifTrue:[
+            aProcess creatorId == id ifTrue:[
+                aProcess isGUIProcess ifTrue:[
+                    aProcess terminateWithAllGUISubprocesses
+                ]
+            ]
+        ]
     ].
 
     "Created: / 28-10-1996 / 20:43:32 / cg"
@@ -1942,21 +1942,21 @@
 terminateAllSubprocessesInGroup
     "terminate all subprocesses which have the receiver process as groupID,
      and their group-children as well.
-     (i.e. all processes in the receivers process group, except for the receiver itself,
+     (i.e. all processes in the receiver's process group, except for the receiver itself,
       and recursively oll of their group processes.)."
 
     id isNil ifTrue:[
-	"/ problem:
-	"/ if receiver is already dead, its id is nil.
-	"/ children are found by looking for processes with a parentID identical to
-	"/ mine - ifNil, system processes are found, which is probably not what you
-	"/ want ...
-	"/ FIX: remember the id (or dont nil it when terminating)
-	"/ requires VM changes.
-	ProcessorScheduler invalidProcessSignal
-	    raiseRequestWith:self
-	    errorString:'process is already dead - cannot determine child processes'.
-	^ self
+        "/ problem:
+        "/ if receiver is already dead, its id is nil.
+        "/ children are found by looking for processes with a parentID identical to
+        "/ mine - ifNil, system processes are found, which is probably not what you
+        "/ want ...
+        "/ FIX: remember the id (or dont nil it when terminating)
+        "/ requires VM changes.
+        ProcessorScheduler invalidProcessSignal
+            raiseRequestWith:self
+            errorString:'process is already dead - cannot determine child processes'.
+        ^ self
     ].
     self terminateAllSubprocessesInGroup:id
 !
@@ -1964,15 +1964,15 @@
 terminateAllSubprocessesInGroup:aGroup
     "terminate all subprocesses which have aGroup as groupID,
      and their group-children as well.
-     (i.e. all processes in the receivers process group, except for the receiver itself,
+     (i.e. all processes in the receiver's process group, except for the receiver itself,
       and recursively oll of their group processes.)."
 
     ProcessorScheduler knownProcesses do:[:aProcess |
-	aProcess ~~ self ifTrue:[
-	    (aProcess processGroupId == aGroup) ifTrue:[
-		aProcess terminateWithAllSubprocessesInGroup
-	    ]
-	]
+        aProcess ~~ self ifTrue:[
+            (aProcess processGroupId == aGroup) ifTrue:[
+                aProcess terminateWithAllSubprocessesInGroup
+            ]
+        ]
     ].
 
     "Created: / 28.10.1996 / 20:43:32 / cg"
@@ -1981,27 +1981,27 @@
 
 terminateGroup
     "terminate the receiver with all of its created subprocesses
-     that are in the receivers process group."
+     that are in the receiver's process group."
 
     id isNil ifTrue:[
-	"/ problem:
-	"/ if receiver is already dead, its id is nil.
-	"/ children are found by looking for processes with a parentID identical to
-	"/ mine - ifNil, system processes are found, which is probably not what you
-	"/ want ...
-	"/ FIX: remember the id (or dont nil it when terminating)
-	"/ requires VM changes.
-	ProcessorScheduler invalidProcessSignal
-	    raiseRequestWith:self
-	    errorString:'process is already dead - cannot determine child processes'.
-	^ self
+        "/ problem:
+        "/ if receiver is already dead, its id is nil.
+        "/ children are found by looking for processes with a parentID identical to
+        "/ mine - ifNil, system processes are found, which is probably not what you
+        "/ want ...
+        "/ FIX: remember the id (or dont nil it when terminating)
+        "/ requires VM changes.
+        ProcessorScheduler invalidProcessSignal
+            raiseRequestWith:self
+            errorString:'process is already dead - cannot determine child processes'.
+        ^ self
     ].
     ProcessorScheduler knownProcesses do:[:aProcess |
-	aProcess ~~ self ifTrue:[
-	    aProcess processGroupId == id ifTrue:[
-		aProcess terminate
-	    ]
-	]
+        aProcess ~~ self ifTrue:[
+            aProcess processGroupId == id ifTrue:[
+                aProcess terminate
+            ]
+        ]
     ].
     self terminate
 !
@@ -2037,33 +2037,33 @@
 
 terminateSubprocesses
     "terminate all the receivers subprocesses
-     (i.e. all processes in the receivers process group, except for
+     (i.e. all processes in the receiver's process group, except for
       the receiver itself)."
 
     id isNil ifTrue:[
-	"/ problem:
-	"/ if receiver is already dead, its id is nil.
-	"/ children are found by looking for processes with a parentID identical to
-	"/ mine - ifNil, system processes are found, which is probably not what you
-	"/ want ...
-	"/ FIX: remember the id (or dont nil it when terminating)
-	"/ requires VM changes.
-	ProcessorScheduler invalidProcessSignal
-	    raiseRequestWith:self
-	    errorString:'process is already dead - cannot determine child processes'.
-	^ self
+        "/ problem:
+        "/ if receiver is already dead, its id is nil.
+        "/ children are found by looking for processes with a parentID identical to
+        "/ mine - ifNil, system processes are found, which is probably not what you
+        "/ want ...
+        "/ FIX: remember the id (or dont nil it when terminating)
+        "/ requires VM changes.
+        ProcessorScheduler invalidProcessSignal
+            raiseRequestWith:self
+            errorString:'process is already dead - cannot determine child processes'.
+        ^ self
     ].
     processGroupId == 0 ifTrue:[
-	ProcessorScheduler invalidProcessSignal
-	    raiseWith:self errorString:'trying to terminate the system process group'.
+        ProcessorScheduler invalidProcessSignal
+            raiseWith:self errorString:'trying to terminate the system process group'.
     ].
     ProcessorScheduler knownProcesses do:[:aProcess |
-	aProcess ~~ self ifTrue:[
-	    (aProcess processGroupId == processGroupId
-	    or:[aProcess processGroupId == id]) ifTrue:[
-		aProcess terminate
-	    ]
-	]
+        aProcess ~~ self ifTrue:[
+            (aProcess processGroupId == processGroupId
+            or:[aProcess processGroupId == id]) ifTrue:[
+                aProcess terminate
+            ]
+        ]
     ].
 
     "Created: 28.10.1996 / 20:41:49 / cg"
@@ -2082,7 +2082,7 @@
 
 terminateWithAllSubprocessesInGroup
     "terminate the receiver with
-     all subprocesses which have the receivers process ID as groupID,
+     all subprocesses which have the receiver's process ID as groupID,
      and their group-children as well.
      (i.e. the receiver plus all processes in the receivers process group,
       and recursively all of their group processes)."
--- a/Project.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Project.st	Sat Mar 26 07:56:10 2016 +0000
@@ -747,7 +747,7 @@
 !Project methodsFor:'changes'!
 
 addClassCommentChangeFor:aClass
-    "add a comment-change for aClass to the receivers changeSet"
+    "add a comment-change for aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -759,7 +759,7 @@
 !
 
 addClassDefinitionChangeFor:aClass
-    "add a class-def-change for aClass to the receivers changeSet"
+    "add a class-def-change for aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -793,7 +793,7 @@
 !
 
 addDoIt:aString
-    "add a doIt to the receivers changeSet"
+    "add a doIt to the receiver's changeSet"
 
     |changeSet|
 
@@ -803,7 +803,7 @@
 !
 
 addInstVarDefinitionChangeFor:aClass
-    "add an instvar-definition-change for aClass to the receivers changeSet"
+    "add an instvar-definition-change for aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -815,7 +815,7 @@
 !
 
 addMethodCategoryChange:aMethod category:newCategory in:aClass
-    "add a method-category-change for aMethod in aClass to the receivers changeSet"
+    "add a method-category-change for aMethod in aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -827,7 +827,7 @@
 !
 
 addMethodChange:aMethod fromOld:oldMethod in:aClass
-    "add a method change in aClass to the receivers changeSet"
+    "add a method change in aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -851,7 +851,7 @@
 !
 
 addMethodPackageChange:aMethod package:newPackage in:aClass
-    "add a method-package-change for aMethod in aClass to the receivers changeSet"
+    "add a method-package-change for aMethod in aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -863,7 +863,7 @@
 !
 
 addMethodPrivacyChange:aMethod in:aClass
-    "add a privacy change for aMethod in aClass to the receivers changeSet"
+    "add a privacy change for aMethod in aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -875,7 +875,7 @@
 !
 
 addPrimitiveDefinitionsChangeFor:aClass
-    "add a primitiveDef change for aClass to the receivers changeSet"
+    "add a primitiveDef change for aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -887,7 +887,7 @@
 !
 
 addPrimitiveFunctionsChangeFor:aClass
-    "add a primitiveFuncs change for aClass to the receivers changeSet"
+    "add a primitiveFuncs change for aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -899,7 +899,7 @@
 !
 
 addPrimitiveVariablesChangeFor:aClass
-    "add a primitiveVars change for aClass to the receivers changeSet"
+    "add a primitiveVars change for aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -911,7 +911,7 @@
 !
 
 addRemoveSelectorChange:aSelector fromOld:oldMethod in:aClass
-    "add a method-remove change in aClass to the receivers changeSet"
+    "add a method-remove change in aClass to the receiver's changeSet"
 
     |changeSet|
 
@@ -923,7 +923,7 @@
 !
 
 addRenameCategoryChangeIn:aClass from:oldCategory to:newCategory
-    "add a category rename change in aClass to the receivers changeSet"
+    "add a category rename change in aClass to the receiver's changeSet"
 
     |changeSet|
 
--- a/ProjectDefinition.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/ProjectDefinition.st	Sat Mar 26 07:56:10 2016 +0000
@@ -6001,7 +6001,7 @@
     myParentPackage := myPackage parentPackage.
     myParentPackage isNil ifTrue:[^ #() ].
 
-    ^ Smalltalk allProjectIDs
+    ^ Smalltalk allPackageIDs
         select:[:projectID |
             |thisPackage|
             thisPackage := projectID asPackageId.
@@ -6025,7 +6025,7 @@
     |myPackage|
 
     myPackage := self package.
-    ^ Smalltalk allProjectIDs
+    ^ Smalltalk allPackageIDs
         select:[:projectID |
             projectID ~= PackageId noProjectID
             and:[ (projectID asPackageId parentPackage) = myPackage ]].
--- a/ReadStream.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/ReadStream.st	Sat Mar 26 07:56:10 2016 +0000
@@ -158,7 +158,7 @@
 !
 
 isReadable
-    "return true, if reading is supported by the recevier.
+    "return true, if reading is supported by the receiver.
      Here, true is always returned."
 
     ^ true
@@ -167,7 +167,7 @@
 !
 
 isWritable
-    "return true, if writing is supported by the recevier.
+    "return true, if writing is supported by the receiver.
      This has to be redefined in concrete subclasses."
 
     ^ false
--- a/SequenceableCollection.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/SequenceableCollection.st	Sat Mar 26 07:56:10 2016 +0000
@@ -393,12 +393,11 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for SequenceableCollection here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == SequenceableCollection
 ! !
 
-
 !SequenceableCollection methodsFor:'Compatibility-Squeak'!
 
 allButFirst
@@ -4136,7 +4135,7 @@
 
 copyToMax:stop
     "return a new collection consisting of receiver's elements
-     from 1 up to (including) index stop, or up to the receivers end,
+     from 1 up to (including) index stop, or up to the receiver's end,
      whichever is smaller (i.e. like copyTo:, but do not err if receiver is smaller"
 
     ^ self copyFrom:1 to:(self size min:stop)
@@ -4533,7 +4532,7 @@
     "return a new collection with newElement inserted after index.
      With a 0 index, newElement is prepended;  
      if index is my size, it is appended.
-     The recevier remains unchanged"
+     The receiver remains unchanged"
 
     ^ ((self copyTo:index) copyWith:newElement),(self copyFrom:index+1).
 
@@ -4549,7 +4548,7 @@
     "return a new collection with newElement inserted after index.
      With a 0 index, newElement is prepended;  
      if index is my size, it is appended.
-     The recevier remains unchanged"
+     The receiver remains unchanged"
 
     ^ self copyWith:newElement insertedAfterIndex:index-1
 
@@ -4566,7 +4565,7 @@
     "return a new collection with aCollection sliced in after index.
      With a 0 index, aString is prepended;  
      if index is my size, it is appended.
-     The recevier remains unchanged"
+     The receiver remains unchanged"
 
     "/ tuning only;
     "/ the code below would work as well (but create a garbage copy of the receiver)
@@ -4587,7 +4586,7 @@
     "return a new collection with aCollection sliced in before index.
      With a 1 index, aString is prepended;  
      if index is my size+1, it is appended.
-     The recevier remains unchanged"
+     The receiver remains unchanged"
 
     ^ self copyWithAll:aCollection insertedAfterIndex:index-1
 
@@ -4848,7 +4847,8 @@
 !
 
 trimForWhich:aCheckBlock
-    "return a copy of myself without leading and trailing elements for which aCheckBlock returns true.
+    "return a copy of myself without leading and trailing elements,
+     for which aCheckBlock returns true.
      Normally, this is mostly used with string receivers."
 
     |startIndex "{ Class: SmallInteger }"
@@ -6907,7 +6907,7 @@
 !
 
 paddedTo:newSize with:padElement
-    "return a new collection consisting of the receivers elements,
+    "return a new collection consisting of the receiver's elements,
      plus pad elements up to length.
      If the receiver's size is equal or greater than the length argument,
      the original receiver is returned unchanged."
@@ -7783,7 +7783,6 @@
     "Created: 14.2.1997 / 16:13:03 / cg"
 ! !
 
-
 !SequenceableCollection methodsFor:'searching'!
 
 detect:aBlock startingAt:startIndex
--- a/SignalSet.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/SignalSet.st	Sat Mar 26 07:56:10 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 IdentitySet subclass:#SignalSet
 	instanceVariableNames:''
 	classVariableNames:''
@@ -115,12 +117,12 @@
 
 accepts:anExceptionHandler
     "return true, if the receiver accepts the argument, aSignal.
-     (i.e. if any of the receivers elements is aSignal or a parent of it).
+     (i.e. if any of the receiver's elements is aSignal or a parent of it).
      False otherwise."
 
     self do:[:eachExceptionHandler |
-	(eachExceptionHandler==anExceptionHandler
-	 or:[eachExceptionHandler accepts:anExceptionHandler]) ifTrue:[^ true].
+        (eachExceptionHandler==anExceptionHandler
+         or:[eachExceptionHandler accepts:anExceptionHandler]) ifTrue:[^ true].
     ].
     ^ false
 !
@@ -175,10 +177,10 @@
 
 handles:anException
     "return true, if the receiver handles the argument, anException.
-     (i.e. if any of the receivers elements handles anException)."
+     (i.e. if any of the receiver's elements handles anException)."
 
     self do:[:eachExceptionHandler|
-	(eachExceptionHandler handles:anException) ifTrue:[^ true]
+        (eachExceptionHandler handles:anException) ifTrue:[^ true]
     ].
     ^ false
 !
@@ -378,7 +380,7 @@
 
 accepts:anExceptionHandler
     "return true, if the receiver accepts the argument, aSignal.
-     (i.e. if any of the receivers elements is aSignal or a parent of it).
+     (i.e. if any of the receiver's elements is aSignal or a parent of it).
      False otherwise. I, the special SetOfAnySignal accepts any (non-query) signal."
 
     ^ anExceptionHandler isExceptionHandler and:[anExceptionHandler isQuerySignal not]
@@ -386,7 +388,7 @@
 
 handles:anException
     "return true, if the receiver handles the argument, anException.
-     (i.e. if any of the receivers elements handles anException).
+     (i.e. if any of the receiver's elements handles anException).
      I, the special SetOfAnySignal handle any (non-query) signal."
 
     ^ anException isNotification not
@@ -402,9 +404,10 @@
 !SignalSet class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SignalSet.st,v 1.47 2014-06-10 10:20:23 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/SignalSet.st,v 1.47 2014-06-10 10:20:23 cg Exp $'
+    ^ '$Header$'
 ! !
+
--- a/Smalltalk.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Smalltalk.st	Sat Mar 26 07:56:10 2016 +0000
@@ -2954,9 +2954,20 @@
     "Modified: / 07-05-2010 / 10:56:09 / cg"
 !
 
+allLoadedPackageIDs
+
+    ^ self allPackageIdsIncludingUnloadedClasses: false
+
+
+    "
+     Smalltalk allLoadedPackageIDs
+    "
+!
+
 allLoadedProjectIDs
-
-    ^ self allProjectsIdsIncludingUnloadedClasses: false
+    <resource: #obsolete>
+    self obsoleteMethodWarning:'use allLoadedPackageIDs'.
+    ^ self allPackageIdsIncludingUnloadedClasses: false
 
 
     "
@@ -2964,10 +2975,66 @@
     "
 !
 
+allPackageIDs
+
+    ^ self allPackageIdsIncludingUnloadedClasses: true
+
+    "
+     Smalltalk allPackageIDs
+    "
+!
+
+allPackageIdsIncludingUnloadedClasses: includeUnloadedClasses
+    "Returns all package ids.
+     Excludes packages coming from unloaded classes if includeUnloadedClasses is false.
+    "
+
+    |allProjects|
+
+    allProjects := Set new.
+    self allClassesDo:[:eachClass |
+        |cls pkg|
+
+        eachClass isRealNameSpace ifFalse:[
+            (includeUnloadedClasses or:[eachClass isLoaded]) ifTrue:[
+                cls := eachClass theNonMetaclass.
+                cls isPrivate ifTrue:[
+                    cls := cls topOwningClass
+                ].
+                pkg := cls package.
+                pkg size > 0 ifTrue:[
+                    allProjects add:pkg.
+                ] ifFalse:[
+                    "/ for now, nameSpaces are not in any package;
+                    "/ this might change. Then, 0-sized packages are
+                    "/ illegal, and the following should be enabled.
+                    "/ self halt
+                ].
+                cls isJavaClass ifFalse:[
+                    cls instAndClassSelectorsAndMethodsDo:[:sel :mthd |
+			| package packageAsSymbol |
+
+			package := mthd package.
+			packageAsSymbol := package asSymbol.
+			allProjects add: packageAsSymbol
+                    ].
+                ].
+            ].
+        ].
+    ].
+    allProjects := allProjects asOrderedCollection sort.
+    ^ allProjects
+
+    "
+     Smalltalk allProjectsIdsIncludingUnloadedClasses: true
+     Smalltalk allProjectsIdsIncludingUnloadedClasses: false
+    "
+!
+
 allProjectIDs
-
-    ^ self allProjectsIdsIncludingUnloadedClasses: true
-
+    <resource: #obsolete>
+    self obsoleteMethodWarning:'use allPackageIDs'.
+    ^ self allPackageIDs
 
     "
      Smalltalk allProjectIDs
@@ -2975,45 +3042,13 @@
 !
 
 allProjectsIdsIncludingUnloadedClasses: includeUnloadedClasses
+    <resource: #obsolete>
     "Returns all projects ids.
      Excludes projects coming from unloaded classes if includeUnloadedClasses is false.
     "
 
-    |allProjects|
-
-    allProjects := Set new.
-    self allClassesDo:[:eachClass |
-	|cls pkg|
-
-	eachClass isRealNameSpace ifFalse:[
-	    (includeUnloadedClasses or:[eachClass isLoaded]) ifTrue:[
-		cls := eachClass theNonMetaclass.
-		cls isPrivate ifTrue:[
-		    cls := cls topOwningClass
-		].
-		pkg := cls package.
-		pkg size > 0 ifTrue:[
-		    allProjects add:pkg.
-		] ifFalse:[
-		    "/ for now, nameSpaces are not in any package;
-		    "/ this might change. Then, 0-sized packages are
-		    "/ illegal, and the following should be enabled.
-		    "/ self halt
-		].
-		cls isJavaClass ifFalse:[
-		    cls instAndClassSelectorsAndMethodsDo:[:sel :mthd |
-			| package packageAsSymbol |
-
-			package := mthd package.
-			packageAsSymbol := package asSymbol.
-			allProjects add: packageAsSymbol
-		    ].
-		].
-	    ].
-	].
-    ].
-    allProjects := allProjects asOrderedCollection sort.
-    ^ allProjects
+    self obsoleteMethodWarning:'use allPackageIdsIncludingUnloadedClasses:'.
+    ^ self allPackageIdsIncludingUnloadedClasses: includeUnloadedClasses
 
     "
      Smalltalk allProjectsIdsIncludingUnloadedClasses: true
--- a/Stream.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Stream.st	Sat Mar 26 07:56:10 2016 +0000
@@ -276,7 +276,6 @@
 ! !
 
 
-
 !Stream methodsFor:'accessing'!
 
 contents
@@ -2518,7 +2517,7 @@
 !
 
 isReadable
-    "return true, if reading is supported by the recevier.
+    "return true, if reading is supported by the receiver.
      This has to be redefined in concrete subclasses."
 
     ^ self subclassResponsibility
@@ -2527,7 +2526,7 @@
 !
 
 isWritable
-    "return true, if writing is supported by the recevier.
+    "return true, if writing is supported by the receiver.
      This has to be redefined in concrete subclasses."
 
     ^ self subclassResponsibility
--- a/StringCollection.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/StringCollection.st	Sat Mar 26 07:56:10 2016 +0000
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 OrderedCollection subclass:#StringCollection
 	instanceVariableNames:''
 	classVariableNames:''
@@ -316,7 +318,7 @@
 !
 
 printString
-    "return the receivers printString"
+    "return the receiver's printString"
 
     ^ self asString
 ! !
@@ -392,7 +394,7 @@
 !
 
 withTabs
-    "return a new stringCollection consisting of the receivers lines,
+    "return a new stringCollection consisting of the receiver's lines,
      where leading spaces are replaced by tabulator characters (assuming 8-col tabs).
      Notice: lines which do not contain leading spaces, are copied by reference to the
              new stringCollection (i.e. shared);
@@ -416,7 +418,7 @@
 !
 
 withTabsExpanded
-    "return a new stringCollection consisting of the receivers lines,
+    "return a new stringCollection consisting of the receiver's lines,
      where tabs are replaced by space characters (assuming 8-col tabs).
      Notice: lines which do not contain any tab, are copied by reference to the
              new stringCollection (i.e. shared);
@@ -436,7 +438,7 @@
 !
 
 withTabsExpanded:n
-    "return a new stringCollection consisting of the receivers lines,
+    "return a new stringCollection consisting of the receiver's lines,
      where tabs are replaced by space characters (assuming n-col tabs).
      Notice: lines which do not contain any tab, are copied by reference to the
              new stringCollection (i.e. shared);
@@ -475,10 +477,10 @@
 !StringCollection class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/StringCollection.st,v 1.51 2014-11-19 15:42:58 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/StringCollection.st,v 1.51 2014-11-19 15:42:58 cg Exp $'
+    ^ '$Header$'
 ! !
 
--- a/Symbol.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/Symbol.st	Sat Mar 26 07:56:10 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -61,7 +59,7 @@
 	which is a symbol consisting of the user visible name, prefixed by ':<ns>::'.
 	The VM's method lookup algorithm contains special handling code for such constructs.
 	Thus, if two methods are stored as 'foo' and ':NS::foo' are present in a class,
-	any send of 'foo' from wíthin the NS-namespace will invoke the second method.
+	any send of 'foo' from wthin the NS-namespace will invoke the second method.
 	Any other send will invoke the first one.
 
 
@@ -151,8 +149,6 @@
 ! !
 
 
-
-
 !Symbol class methodsFor:'queries'!
 
 findInterned:aString
@@ -594,7 +590,7 @@
 !
 
 asSymbol
-    "Return a unique symbol with the name taken from the receivers characters.
+    "Return a unique symbol with the name taken from the receiver's characters.
      Since I am a symbol - just return myself"
 
     ^ self
@@ -917,3 +913,4 @@
 version_SVN
     ^ '$ Id: Symbol.st 10648 2011-06-23 15:55:10Z vranyj1  $'
 ! !
+
--- a/UninterpretedBytes.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/UninterpretedBytes.st	Sat Mar 26 07:56:10 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
               All Rights Reserved
@@ -409,7 +407,7 @@
 isAbstract
     "Return if this class is an abstract class.
      True is returned for UninterpretedBytes here; false for subclasses.
-     Abstract subclasses must redefine again."
+     Abstract subclasses must redefine this again."
 
     ^ self == UninterpretedBytes
 !
@@ -745,7 +743,7 @@
 longLongAt:index
     "return the 8-bytes starting at index as a signed Integer.
      The index is a smalltalk index (i.e. 1-based).
-     The value is retrieved in the machineÄs natural byte order.
+     The value is retrieved in the machineÄs natural byte order.
      This may be worth a primitive."
 
     ^ self signedInt64At:index MSB:IsBigEndian
--- a/UserPreferences.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/UserPreferences.st	Sat Mar 26 07:56:10 2016 +0000
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1998 by eXept Software AG
 	      All Rights Reserved
@@ -840,19 +842,6 @@
     "Modified: / 15-01-2012 / 14:26:53 / cg"
 ! !
 
-
-
-
-!UserPreferences methodsFor:'accessing-changes & history'!
-
-historyManagerAllowEditOfHistory:aBoolean
-    "useful if you have 'beginner students', to prevent them from changing the history"
-
-    self 
-        at: #'history-manager.allow-edit-of-history'
-        put:aBoolean
-! !
-
 !UserPreferences methodsFor:'accessing-locale'!
 
 dateInputFormat
@@ -1577,6 +1566,7 @@
     ^ DiffCodeView
 ! !
 
+
 !UserPreferences methodsFor:'accessing-prefs-UI'!
 
 allowMouseWheelZoom
@@ -3944,6 +3934,16 @@
     "Created: / 17-02-2011 / 14:18:01 / cg"
 ! !
 
+!UserPreferences methodsFor:'accessing-prefs-changes & history'!
+
+historyManagerAllowEditOfHistory:aBoolean
+    "useful if you have 'beginner students', to prevent them from changing the history"
+
+    self 
+        at: #'history-manager.allow-edit-of-history'
+        put:aBoolean
+! !
+
 !UserPreferences methodsFor:'accessing-prefs-code'!
 
 categoryForMenuActionsMethods
@@ -4848,6 +4848,20 @@
     "
 ! !
 
+!UserPreferences methodsFor:'accessing-prefs-startup'!
+
+autoloadedPackages
+    "list of package names, which are automatically loaded upon startup"
+
+    ^ self at:#autoloadedPackages ifAbsent:[#()]
+!
+
+autoloadedPackages:aCollectionOfPackageNames
+    "list of package names, which are automatically loaded upon startup"
+
+    self at:#autoloadedPackages put:aCollectionOfPackageNames
+! !
+
 !UserPreferences methodsFor:'accessing-prefs-times'!
 
 timeToAutoExpandItemsWhenDraggingOver
--- a/WriteStream.st	Fri Mar 25 06:29:08 2016 +0000
+++ b/WriteStream.st	Sat Mar 26 07:56:10 2016 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -295,7 +293,7 @@
 !
 
 isWritable
-    "return true, if writing is supported by the recevier.
+    "return true, if writing is supported by the receiver.
      Always return true here"
 
     ^ true
@@ -644,9 +642,10 @@
 !WriteStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WriteStream.st,v 1.97 2015-04-27 17:04:19 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/WriteStream.st,v 1.97 2015-04-27 17:04:19 cg Exp $'
+    ^ '$Header$'
 ! !
+