Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Mon, 03 Oct 2016 12:44:41 +0100
branchjv
changeset 20578 39641ba8d6e0
parent 20577 a27e7b3031cb (current diff)
parent 20503 e598faa37310 (diff)
child 20579 9add81aadb7a
Merge
AbstractOperatingSystem.st
AmbiguousMessage.st
ArithmeticError.st
AssertionFailedError.st
CachingRegistry.st
CharacterArray.st
CharacterEncoder.st
Class.st
ClassBuildError.st
ClassBuilder.st
ClassDescription.st
CompiledCode.st
Complex.st
ContextError.st
Date.st
DirectoryStream.st
ElementBoundsError.st
EncodedStream.st
ExecutionError.st
ExternalBytes.st
ExternalStream.st
FileStream.st
Filename.st
FixedPoint.st
Float.st
Fraction.st
GenericException.st
IndexNotFoundError.st
LargeInteger.st
LongFloat.st
Make.proto
Make.spec
MessageNotUnderstood.st
MiniDebugger.st
MiniLogger.st
NoModificationError.st
NonIntegerIndexError.st
NotFoundError.st
Number.st
Object.st
ObjectMemory.st
PositionableStream.st
ProjectDefinition.st
ReadWriteStream.st
Semaphore.st
ShortFloat.st
Signal.st
SignalError.st
StandaloneStartup.st
Stream.st
String.st
StringCollection.st
SubclassResponsibilityError.st
Timestamp.st
UnimplementedFunctionalityError.st
UnixOperatingSystem.st
Win32OperatingSystem.st
WriteStream.st
ZeroDivide.st
abbrev.stc
bc.mak
libInit.cc
stx_libbasic.st
--- a/AbstractOperatingSystem.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/AbstractOperatingSystem.st	Mon Oct 03 12:44:41 2016 +0100
@@ -3490,7 +3490,7 @@
 
 pathNameOf:pathName
     "return the pathName of the argument, aPathString,
-     - thats the full pathname of the directory, starting at '/'.
+     - that's the full pathname of the directory, starting at '/'.
      This method needs the path to be valid
      (i.e. all directories must exist, be readable and executable).
      Notice: if symbolic links are involved, the result may look different
@@ -3529,7 +3529,7 @@
 
 volumeNameOf:aPathString
     "return the volumeName of the argument, aPath
-     - thats the name of the volume where aPath is.
+     - that's the name of the volume where aPath is.
      Not all OperatingSystems support/use volumes; on unix,
      this always returns an empty string."
 
@@ -6813,7 +6813,7 @@
 
 getDocumentsDirectory
     "return your documents directory.
-     Under windows, thats the real 'Documents' or 'My Documents'.
+     Under windows, that's the real 'Documents' or 'My Documents'.
      The fallback here returns the users home directory."
 
     "{ Pragma: +optSpace }"
@@ -6828,7 +6828,7 @@
 getEffectiveGroupID
     "{ Pragma: +optSpace }"
 
-    "return the current users (thats you) effective numeric group id.
+    "return the current users (that's you) effective numeric group id.
      This is only different from getGroupID, if you have ST/X running
      as a setuid program (of which you should think about twice)."
 
@@ -6842,7 +6842,7 @@
 getEffectiveUserID
     "{ Pragma: +optSpace }"
 
-    "return the current users (thats you) effective numeric user id.
+    "return the current users (that's you) effective numeric user id.
      This is only different from getUserID, if you have ST/X running
      as a setuid program (of which you should think about twice)."
 
@@ -6856,7 +6856,7 @@
 getFullUserName
     "{ Pragma: +optSpace }"
 
-    "return a string with the users full name (thats you) - if available.
+    "return a string with the users full name (that's you) - if available.
      If not, return the login name as a fallBack."
 
     ^ self getFullUserNameFromID:(self getUserID)
@@ -6889,7 +6889,7 @@
 getGroupID
     "{ Pragma: +optSpace }"
 
-    "return the current users (thats you) numeric group id"
+    "return the current users (that's you) numeric group id"
 
     ^ 1 "/ just a dummy for systems which do not have userIDs
 
@@ -6927,7 +6927,7 @@
 getLoginName
     "{ Pragma: +optSpace }"
 
-    "return a string with the users login name (thats yours)"
+    "return a string with the users login name (that's yours)"
 
     self subclassResponsibility
 !
@@ -6935,7 +6935,7 @@
 getUserID
     "{ Pragma: +optSpace }"
 
-    "return the current users (thats you) numeric user id"
+    "return the current users (that's you) numeric user id"
 
     ^ 1 "just a dummy for systems which do not have userIDs"
 
--- a/AmbiguousMessage.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/AmbiguousMessage.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2010 by Jan Vrany, SWING Research Group. CTU in Prague
               All Rights Reserved
@@ -25,7 +27,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-ProceedableError subclass:#AmbiguousMessage
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#AmbiguousMessage
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -72,13 +76,23 @@
 "
 ! !
 
+!AmbiguousMessage class methodsFor:'testing'!
+
+isProgramError
+    "redefined in all exceptions which are programmer's errors,
+     and which should probably not be ignored.
+     I.e. a global error handler should reject and let a debugger get control."
+
+    ^ true
+! !
+
 !AmbiguousMessage class methodsFor:'documentation'!
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/AmbiguousMessage.st,v 1.4 2013-12-24 10:40:54 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
-    ^ '$Id: AmbiguousMessage.st,v 1.4 2013-12-24 10:40:54 cg Exp $'
+    ^ '$Id$'
 ! !
 
--- a/ArithmeticError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ArithmeticError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2005 by eXept Software AG
               All Rights Reserved
@@ -11,7 +13,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-ProceedableError subclass:#ArithmeticError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#ArithmeticError
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -40,11 +44,20 @@
 "
 ! !
 
+!ArithmeticError class methodsFor:'testing'!
+
+isProgramError
+    "redefined in all exceptions which are programmer's errors,
+     and which should probably not be ignored.
+     I.e. a global error handler should reject and let a debugger get control."
+
+    ^ true
+! !
 
 !ArithmeticError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ArithmeticError.st,v 1.8 2013-03-13 23:44:07 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/AssertionFailedError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/AssertionFailedError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2007 by eXept Software AG
               All Rights Reserved
@@ -11,7 +13,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-ProceedableError subclass:#AssertionFailedError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#AssertionFailedError
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -40,10 +44,20 @@
 "
 ! !
 
+!AssertionFailedError class methodsFor:'testing'!
+
+isProgramError
+    "redefined in all exceptions which are programmer's errors,
+     and which should probably not be ignored.
+     I.e. a global error handler should reject and let a debugger get control."
+
+    ^ true
+! !
+
 !AssertionFailedError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/AssertionFailedError.st,v 1.3 2008/09/30 18:09:46 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/CachingRegistry.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/CachingRegistry.st	Mon Oct 03 12:44:41 2016 +0100
@@ -76,9 +76,28 @@
 detect:aBlock ifNone:exceptionValue
     "... additionaly move it to the front of the LRU chain"
 
+    |cnt|
+
+    "first a quick lookup 
+     (most recent entry is at the end, because #removeIdentical makes room at the end)..."
+
+    cnt := 1.
+    keptReferences reverseDo:[:obj|
+        (aBlock value:obj) ifTrue:[
+            "if not at the end, put it to the end.
+             but avoid to much remove/add actions"
+            cnt > (cacheSize // 4) ifTrue:[
+                keptReferences removeIdentical:obj ifAbsent:[].
+                keptReferences addLast:obj.
+            ].
+            ^ obj
+        ].
+        cnt := cnt + 1.
+    ].
+
+    "check the whole registry..."
     keyArray validElementsDo:[:obj |
         (obj ~~ DeletedEntry and:[aBlock value:obj]) ifTrue:[
-            keptReferences removeIdentical:obj ifAbsent:[].
             keptReferences size >= cacheSize ifTrue:[
                 keptReferences removeFirst.
             ].
--- a/CharacterArray.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/CharacterArray.st	Mon Oct 03 12:44:41 2016 +0100
@@ -3109,6 +3109,35 @@
     ^ ba
 !
 
+asCanonicalizedFilename
+    "return a Filename with pathname taken from the receiver.
+     The filename is canonicalized, meaning that it cares for trailing directory separators,
+     '.' components etc."
+
+    ^ self asFilename asCanonicalizedFilename
+
+    "on windows:
+     'c:\foo\bar' asFilename
+     'c:\foo\bar\' asFilename
+     'c:\foo\bar\..\baz' asFilename
+     'c:\foo\bar\..\baz\.' asFilename
+     'c:\foo\bar' asCanonicalizedFilename
+     'c:\foo\bar\' asCanonicalizedFilename
+     'c:\foo\bar\..\baz' asCanonicalizedFilename
+     'c:\foo\bar\..\baz\.' asCanonicalizedFilename
+    
+    on unix:
+     '/foo/bar' asFilename
+     '/foo/bar/' asFilename
+     '/foo/bar/../baz' asFilename
+     '/foo/bar/../baz/.' asFilename
+     '/foo/bar' asCanonicalizedFilename
+     '/foo/bar/' asCanonicalizedFilename
+     '/foo/bar/../baz' asCanonicalizedFilename
+     '/foo/bar/../baz/.' asCanonicalizedFilename
+    "
+!
+
 asCollectionOfLines
     "return a collection containing the lines (separated by cr)
      of the receiver. If multiple cr's occur in a row, the result will
--- a/CharacterEncoder.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/CharacterEncoder.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2004 by eXept Software AG
               All Rights Reserved
@@ -1123,7 +1125,7 @@
         encoding: name
      within the given buffer 
      (which is usually the first few bytes of a textFile).
-     If thats not found, use heuristics (in CharacterArray) to guess.
+     If that's not found, use heuristics (in CharacterArray) to guess.
      Return a symbol like #utf8."
 
     |s buffer n "{Class: SmallInteger }"|
--- a/Class.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Class.st	Mon Oct 03 12:44:41 2016 +0100
@@ -5579,7 +5579,7 @@
     ] ifFalse:[
         "/
         "/ if its a method returning the string,
-        "/ thats the returned value
+        "/ that's the returned value
         "/
         versionFromCode := versionMethod valueWithReceiver:cls arguments:#().
         versionFromCode isString ifFalse:[
--- a/ClassBuildError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ClassBuildError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2009 by eXept Software AG
               All Rights Reserved
@@ -11,7 +13,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-Error subclass:#ClassBuildError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#ClassBuildError
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -34,12 +38,23 @@
 "
 ! !
 
+!ClassBuildError class methodsFor:'testing'!
+
+isProgramError
+    "redefined in all exceptions which are programmer's errors,
+     and which should probably not be ignored.
+     I.e. a global error handler should reject and let a debugger get control."
+
+    ^ true
+! !
+
 !ClassBuildError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ClassBuildError.st,v 1.2 2009-09-29 19:32:30 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/ClassBuildError.st,v 1.2 2009-09-29 19:32:30 cg Exp $'
+    ^ '$Header$'
 ! !
+
--- a/ClassBuilder.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ClassBuilder.st	Mon Oct 03 12:44:41 2016 +0100
@@ -599,7 +599,7 @@
     "/ NOTICE:
     "/ I dont like the confirmers there - we need a notifying: argument, to give
     "/ the outer codeview a chance to highlight the error.
-    "/ (but thats how its defined in the book - maybe I will change anyway).
+    "/ (but that's how its defined in the book - maybe I will change anyway).
     "/ - or use upQueries in future versions.
 
     oldClass isNil ifTrue:[
@@ -2118,9 +2118,9 @@
 checkConventionsFor:className subClassOf:aClass instVarNames:instVarNameString classVarNames:classVarNameString
     "Check for some 'considered bad-style' things, like lower case names.
      NOTICE:
-     I dont like the confirmers below - we need a notifying: argument, to give
+     I don't like the confirmers below - we need a notifying: argument, to give
      the outer codeview a chance to highlight the error.
-     (but thats how its defined in the book - maybe I will change it anyway).
+     (but that's how its defined in the book - maybe I will change it anyway).
     "
 
     |names idx what doChecks answ|
--- a/ClassDescription.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ClassDescription.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -205,7 +207,7 @@
         UpdateChangeListQuerySignal handlerBlock:[:ex | ex proceedWith:UpdatingChanges].
 
         NameSpaceQuerySignal isNil ifTrue:[
-            "This could be used BEFORE initialize has been invoked - thats why we initialize
+            "This could be used BEFORE initialize has been invoked - that's why we initialize
              the class var there."
             NameSpaceQuerySignal := self nameSpaceQuerySignal
         ].
@@ -402,7 +404,7 @@
 nameSpaceQuerySignal
     "return the signal used as an upQuery for the current nameSpace.
      Will be used when filing in code.
-     This could be used BEFORE initialize has been invoked - thats why we do not
+     This could be used BEFORE initialize has been invoked - that's why we do not
      simply return the class var here."
 
     NameSpaceQuerySignal isNil ifTrue:[
@@ -487,7 +489,7 @@
 usedNameSpaceQuerySignal
     "return the signal used as an upQuery for the used nameSpace.
      Will be used when filing in code.
-     This could be used BEFORE initialize has been invoked - thats why we do not
+     This could be used BEFORE initialize has been invoked - that's why we do not
      simply return the class var here."
 
     UsedNameSpaceQuerySignal isNil ifTrue:[
@@ -978,7 +980,7 @@
 
     |s|
 
-    s := WriteStream on:(String new).
+    s := WriteStream on:''.
     self fileOutDefinitionOn:s.
     ^ s contents
 
--- a/CompiledCode.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/CompiledCode.st	Mon Oct 03 12:44:41 2016 +0100
@@ -507,7 +507,7 @@
 
 mclass
     "return the class of the receiver's home method.
-     Thats the class of the method where the block was compiled."
+     That's the class of the method where the block was compiled."
 
     ^ self homeMethod mclass
 
@@ -1929,17 +1929,17 @@
 !
 
 referencesLiteral:aLiteral
-    "return true, if this method directly references the given literal directly
+    "return true, if this method references the given literal directly
      (i.e. a flat search, which does not look deeper into literal arrays)."
 
     |lit|
 
     lit := aLiteral.
     aLiteral isAssociation ifTrue:[
-	"/ for ST80 compatibility (where variableBindings are used...)
-	lit := lit key
+        "/ for ST80 compatibility (where variableBindings are used...)
+        lit := lit key
     ].
-    ^ (self literalsDetect:[:mthdLit| mthdLit == lit] ifNone:[false]) ~~ false.
+    ^ (self literalsDetect:[:mthdLit| mthdLit == lit] ifNone:[nil]) ~~ nil.
 
     "
      (CompiledCode compiledMethodAt:#referencesLiteral:) referencesGlobal:#literalsDetect:ifNone:
--- a/Complex.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Complex.st	Mon Oct 03 12:44:41 2016 +0100
@@ -304,7 +304,7 @@
 
 abs
     "Return the magnitude (or absolute value) of the complex number
-     (thats the distance from the origin in the complex plane)."
+     (that's the distance from the origin in the complex plane)."
 
     ^ (real * real + (imaginary * imaginary)) sqrt
 
--- a/ContextError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ContextError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -11,7 +11,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-ProceedableError subclass:#ContextError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#ContextError
 	instanceVariableNames:'context'
 	classVariableNames:''
 	poolDictionaries:''
@@ -43,7 +45,7 @@
 !ContextError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ContextError.st,v 1.5 2013-12-24 10:39:33 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/Date.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Date.st	Mon Oct 03 12:44:41 2016 +0100
@@ -925,7 +925,6 @@
     "
 ! !
 
-
 !Date class methodsFor:'change & update'!
 
 update:something with:aParameter from:changedObject
@@ -1897,7 +1896,6 @@
     "Modified: 8.10.1996 / 19:25:39 / cg"
 ! !
 
-
 !Date class methodsFor:'private'!
 
 dayAbbrevsForLanguage:languageOrNilForDefault
@@ -2107,14 +2105,13 @@
 
     "
      Date fromOSTime:0              -> on UNIX: this should return 1st Jan 1970
-                                       thats where Unix time starts
+                                       that's where Unix time starts
                                        On other systems, it may be something different.
 
      Date fromOSTime:(24*60*60*1000) -> on UNIX: the day after
     "
 ! !
 
-
 !Date methodsFor:'Compatibility-ANSI'!
 
 dayOfWeek
@@ -3274,7 +3271,6 @@
 ! !
 
 
-
 !Date methodsFor:'obsolete'!
 
 asAbsoluteTime
@@ -3345,7 +3341,6 @@
     ^ self addDays:days
 ! !
 
-
 !Date methodsFor:'printing & storing'!
 
 addPrintBindingsTo:aDictionary
--- a/DirectoryStream.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/DirectoryStream.st	Mon Oct 03 12:44:41 2016 +0100
@@ -143,7 +143,7 @@
 # define __HANDLEVal(o)  (HANDLE)__externalAddressVal(o)
 // extern OBJ FileTimeToOsTime();
 extern OBJ FileTimeToOsTime1970();
-#endif /* WIN32 */
+#endif /* __win32__ */
 
 #include "stxOSDefs.h"
 %}
--- a/ElementBoundsError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ElementBoundsError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2001 by eXept Software AG
               All Rights Reserved
@@ -11,7 +13,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-Error subclass:#ElementBoundsError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#ElementBoundsError
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -50,16 +54,27 @@
     NotifierString := 'element not appropriate or out of bounds'.
 ! !
 
+!ElementBoundsError class methodsFor:'testing'!
+
+isProgramError
+    "redefined in all exceptions which are programmer's errors,
+     and which should probably not be ignored.
+     I.e. a global error handler should reject and let a debugger get control."
+
+    ^ true
+! !
+
 !ElementBoundsError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ElementBoundsError.st,v 1.1 2004/04/23 11:16:20 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
     ^ '$Id: ElementBoundsError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
+
 ElementBoundsError initialize!
 
 
--- a/EncodedStream.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/EncodedStream.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2004 by eXept Software AG
               All Rights Reserved
@@ -55,7 +53,7 @@
     "
      |s|
      s := EncodedStream stream:Transcript encoder:(CharacterEncoder encoderToEncodeFrom:#utf8 into:#unicode).
-     s nextPutAll:('öäü' utf8Encoded)
+     s nextPutAll:('öäü' utf8Encoded)
     "
 !
 
@@ -66,7 +64,7 @@
      |baseStream s|
      baseStream := '' readWriteStream.
      s := EncodedStream stream:baseStream encoding:#utf8.
-     s nextPutAll:'öäü'.
+     s nextPutAll:'öäü'.
      baseStream reset; contents.
     "
 ! !
@@ -161,7 +159,7 @@
 !
 
 pathName
-    "if our base stream hat a pathname, delegate..."
+    "if our base stream has a pathname, delegate..."
 
     stream isNil ifTrue:[
         ^ nil.
--- a/ExecutionError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ExecutionError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2003 by eXept Software AG
               All Rights Reserved
@@ -11,6 +13,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 ProceedableError subclass:#ExecutionError
 	instanceVariableNames:''
 	classVariableNames:''
@@ -46,16 +50,27 @@
     NotifierString := 'execution error'.
 ! !
 
+!ExecutionError class methodsFor:'testing'!
+
+isProgramError
+    "redefined in all exceptions which are programmer's errors,
+     and which should probably not be ignored.
+     I.e. a global error handler should reject and let a debugger get control."
+
+    ^ true
+! !
+
 !ExecutionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ExecutionError.st,v 1.4 2003/09/05 10:26:58 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
     ^ '$Id: ExecutionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
+
 ExecutionError initialize!
 
 
--- a/ExternalBytes.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ExternalBytes.st	Mon Oct 03 12:44:41 2016 +0100
@@ -648,6 +648,20 @@
     "
 !
 
+sizeofEnums
+    "return the number of bytes used by the machine's native enums.
+     Be aware, that this can be adjusted in some compilers via the __packed__ attribute;
+     So better double check..."
+
+%{  /* NOCONTEXT */
+    enum foo { bla1, bla2 } foo;
+    RETURN (__mkSmallInteger( sizeof(foo)));
+%}
+    "
+     ExternalBytes sizeofEnums
+    "
+!
+
 sizeofFloat
     "return the number of bytes used by the machine's native floats"
 
@@ -866,10 +880,10 @@
     |idx byte s|
 
     idx := 1.
-    s := WriteStream on:String new.
+    s := WriteStream on:''.
     [(byte := self at:idx) ~~ 0] whileTrue:[
-	s nextPut:(Character value:byte).
-	idx := idx + 1.
+        s nextPut:(Character value:byte).
+        idx := idx + 1.
     ].
     ^ s contents
 !
--- a/ExternalStream.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ExternalStream.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -1393,37 +1395,37 @@
 
     [Instance variables:]
 
-	handleType      <Symbol>        desribes what handle is:
-					    win32: #fileHandle, #socketHandle,
-						   #filePointer, #socketFilePointer, #pipeFilePointer
-					    unix: #filePointer, #socketFilePointer, #pipeFilePointer
-					needed for win32, which uses different APIs for the different handles (sigh)
-	handle          <Integer>       used to be always a filePointer somehow mapped to an integer (FILE* - not the fd);
-					now, either a filePointer or a handle (win32)
-	mode            <Symbol>        #readwrite, #readonly or #writeonly
-	buffered        <Boolean>       true, if buffered (i.e. collects characters - does
-					not output immediately)
-	binary          <Boolean>       true if in binary mode (reads bytes instead of chars)
-	eolMode         <Symbol>        one of nil, #nl, #cr or #crlf.
-					determines how lines should be terminated.
-					nil -> newLine (as in Unix);
-					#crlf -> with cr-lf (as in MSDOS)
-					#cr -> with cr (as in VMS)
-	hitEOF          <Boolean>       true, if EOF was reached
-
-	lastErrorNumber <Integer>       the value of errno (only valid right after the error -
-					updated with next i/o operation)
+        handleType      <Symbol>        desribes what handle is:
+                                            win32: #fileHandle, #socketHandle,
+                                                   #filePointer, #socketFilePointer, #pipeFilePointer
+                                            unix: #filePointer, #socketFilePointer, #pipeFilePointer
+                                        needed for win32, which uses different APIs for the different handles (sigh)
+        handle          <Integer>       used to be always a filePointer somehow mapped to an integer (FILE* - not the fd);
+                                        now, either a filePointer or a handle (win32)
+        mode            <Symbol>        #readwrite, #readonly or #writeonly
+        buffered        <Boolean>       true, if buffered (i.e. collects characters - does
+                                        not output immediately)
+        binary          <Boolean>       true if in binary mode (reads bytes instead of chars)
+        eolMode         <Symbol>        one of nil, #nl, #cr or #crlf.
+                                        determines how lines should be terminated.
+                                        nil -> newLine (as in Unix);
+                                        #crlf -> with cr-lf (as in MSDOS)
+                                        #cr -> with cr (as in VMS)
+        hitEOF          <Boolean>       true, if EOF was reached
+
+        lastErrorNumber <Integer>       the value of errno (only valid right after the error -
+                                        updated with next i/o operation)
 
     [Class variables:]
-	Lobby           <Registry>      keeps track of used ext-streams (to free up FILE*'s)
-
-	StreamErrorSignal       <Signal> parent of all stream errors (see Stream class)
-	InvalidReadSignal       <Signal> raised on read from writeonly stream
-	InvalidWriteSignal      <Signal> raised on write to readonly stream
-	InvalidModeSignal       <Signal> raised on text I/O with binary-stream
-					 or binary I/O with text-stream
-	OpenErrorSignal         <Signal> raised if open fails
-	StreamNotOpenSignal     <Signal> raised on I/O with non-open stream
+        Lobby           <Registry>      keeps track of used ext-streams (to free up FILE*'s)
+
+        StreamErrorSignal       <Signal> parent of all stream errors (see Stream class)
+        InvalidReadSignal       <Signal> raised on read from writeonly stream
+        InvalidWriteSignal      <Signal> raised on write to readonly stream
+        InvalidModeSignal       <Signal> raised on text I/O with binary-stream
+                                         or binary I/O with text-stream
+        OpenErrorSignal         <Signal> raised if open fails
+        StreamNotOpenSignal     <Signal> raised on I/O with non-open stream
 
     Additional notes:
       This class is implemented using the underlying stdio-c library package, which
@@ -1437,7 +1439,7 @@
       occur while reading (for example, timer interrupts) - on real unixes (i.e. BSD) the signal
       is handled transparently - on SYS5.3 (i.e. non unixes :-) the read operation returns
       an error and errno is set to EINTR.
-      Thats what the ugly code around all getc-calls is for ...
+      That's what the ugly code around all getc-calls is for ...
       Since things get more and more ugly - we will rewrite ExternalStream
       completely, to NOT use any stdio stuff (and do its buffering itself).
 
@@ -1457,12 +1459,12 @@
       fread/fgetc and fwrite/putc respectively.
 
     [author:]
-	Claus Gittinger
-	Stefan Vogel (many, many fixes ...)
+        Claus Gittinger
+        Stefan Vogel (many, many fixes ...)
 
     [see also:]
-	FileStream Socket PipeStream
-	Filename OperatingSystem
+        FileStream Socket PipeStream
+        Filename OperatingSystem
 "
 !
 
@@ -4625,7 +4627,7 @@
     "
         (FileStream newTemporary
             nextPutUtf16:$B;
-            nextPutUtf16:$;
+            nextPutUtf16:$Ä;
             nextPutUtf16:(Character codePoint:16r10CCCC);
             reset;
             binary;
@@ -6577,7 +6579,7 @@
     ].
 
     "
-	'Bnnigheim' asUnicode16String errorPrintCR
+	'Bönnigheim' asUnicode16String errorPrintCR
     "
 !
 
--- a/FileStream.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/FileStream.st	Mon Oct 03 12:44:41 2016 +0100
@@ -2009,7 +2009,7 @@
 
 collectionSize
     "common stream protocol: return the size of the stream;
-     thats the number of bytes of the file."
+     that's the number of bytes of the file."
 
     ^ self fileSize.
 !
@@ -2091,7 +2091,7 @@
 
 size
     "common stream protocol: return the size of the stream;
-     thats the number of bytes of the file."
+     that's the number of bytes of the file."
 
     ^ self fileSize.
 
--- a/Filename.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Filename.st	Mon Oct 03 12:44:41 2016 +0100
@@ -17,7 +17,7 @@
 
 Object subclass:#Filename
 	instanceVariableNames:'nameString'
-	classVariableNames:'TempDirectory DefaultTempDirectory ConcreteClass'
+	classVariableNames:'ConcreteClass DefaultTempDirectory TempDirectory'
 	poolDictionaries:''
 	category:'System-Support'
 !
@@ -381,14 +381,14 @@
 
 desktopDirectory
     "return your desktop directory.
-     Under windows, thats the real desktop directory;
+     Under windows, that's the real desktop directory;
      under other OperatingSystems, the home directory is returned."
 
     |s|
 
     s := OperatingSystem getDesktopDirectory.
     s isNil ifTrue:[
-	^ self homeDirectory
+        ^ self homeDirectory
     ].
     ^ self named:s
 
@@ -401,14 +401,14 @@
 
 documentsDirectory
     "return your documents directory.
-     Under windows, thats the real 'Documents' or 'My Documents';
+     Under windows, that's the real 'Documents' or 'My Documents';
      under other OperatingSystems, the home directory is returned."
 
     |s|
 
     s := OperatingSystem getDocumentsDirectory.
     s isNil ifTrue:[
-	^ self homeDirectory
+        ^ self homeDirectory
     ].
     ^ self named:s
 
@@ -2052,9 +2052,9 @@
 !
 
 asFilename
-    "return the receiver converted to a filename; here, thats the receiver itself."
-
-    "Thats pretty easy here :-)"
+    "return the receiver converted to a filename; here, that's the receiver itself."
+
+    "That's pretty easy here :-)"
     ^ self
 
     "Modified: 12.11.1996 / 12:40:03 / cg"
@@ -2087,16 +2087,18 @@
     fn := baseFn := self.
     nextSeqNr := 0.
     [ fn exists ] whileTrue:[
-        |newFn|
+        |newFn suff|
         
         nextSeqNr := (nextSeqNr ? 0) + 1.
-        fn := (baseFn withoutSuffix name,'_',nextSeqNr asString) asFilename withSuffix:baseFn suffix.
+        suff := baseFn suffix.
+        suff notEmpty ifTrue:[ suff := '.',suff ].
+        fn := self class named:((baseFn withoutSuffix name,'_',nextSeqNr asString),suff).
     ].
     ^ fn
 
     "
      'aaa.txt' asFilename contents:'bla'.
-     'aaa.txt' asFilename asUniqueFilename contents:'bla2'.
+     'aaa.1.2.3.apk.txt' asFilename asUniqueFilename contents:'bla2'.
      'aaa.txt' asFilename asUniqueFilename contents:'bla3'.
      'aaa.txt' asFilename asUniqueFilename contents:'bla4'.
      #('aaa.txt' 'aaa_1.txt' 'aaa_2.txt' 'aaa_3.txt') do:[:f | f asFilename delete].  
@@ -4651,6 +4653,9 @@
      '/bin/ls' asFilename isExecutable
      '/tmp' asFilename isExecutableProgram
      '/bin/ls' asFilename isExecutableProgram
+     
+     'ls' asFilename isExecutableProgram
+     OperatingSystem canExecuteCommand:'ls'
     "
 !
 
@@ -4882,7 +4887,7 @@
 
 baseName
     "return my baseName as a string.
-     - thats the file/directory name without leading parent-dirs.
+     - that's the file/directory name without leading parent-dirs.
      (i.e. '/usr/lib/st/file' asFilename baseName -> 'file'
        and '/usr/lib'         asFilename baseName -> lib).
      This method does not check if the path is valid.
@@ -4896,12 +4901,12 @@
     sep := self separator.
     len := nameString size.
     ((len == 1) and:[(nameString at:1) == sep]) ifTrue:[
-	^ nameString
+        ^ nameString
     ].
 
     endIdx := len.
     len > 1 ifTrue:[
-	(nameString at:len) == sep ifTrue:[endIdx := endIdx - 1].
+        (nameString at:len) == sep ifTrue:[endIdx := endIdx - 1].
     ].
     index := nameString lastIndexOf:sep startingAt:len-1.
     ^ nameString copyFrom:(index+1) to:endIdx
@@ -4926,7 +4931,7 @@
 
 directory
     "return the directory name part of the file/directory as a new filename.
-     - thats a filename for the directory where the file/dir represented by
+     - that's a filename for the directory where the file/dir represented by
        the receiver is contained in.
      (this is almost equivalent to #directoryName or #head, but returns
       a Filename instance instead of a string )."
@@ -4948,7 +4953,7 @@
 
 directoryName
     "return the directory name part of the file/directory as a string.
-     - thats the name of the directory where the file/dir represented by
+     - that's the name of the directory where the file/dir represented by
        the receiver is contained in.
      This method does not check if the path is valid.
 
@@ -4966,10 +4971,10 @@
     sep := self separator.
     sepString := sep asString.
     (nameString = sepString) ifTrue:[
-	"/
-	"/ the trivial '/' case
-	"/
-	^ sepString
+        "/
+        "/ the trivial '/' case
+        "/
+        ^ sepString
     ].
 
     "/
@@ -4977,10 +4982,10 @@
     "/
     p := nameString.
     [p endsWith:sep] whileTrue:[
-	(p = sepString) ifTrue:[
-	    ^ sepString
-	].
-	p := p copyButLast:1
+        (p = sepString) ifTrue:[
+            ^ sepString
+        ].
+        p := p copyButLast:1
     ].
 
     parentDirectoryString := self class parentDirectoryName.
@@ -4988,24 +4993,24 @@
     "/ strip off trailing components
     index := p lastIndexOf:sep startingAt:p size.
     index == 0 ifTrue:[
-	"/ no separator found
-	p = '.' ifTrue:[
-	    ^ parentDirectoryString
-	].
-	p = '..' ifTrue:[
-	    ^ parentDirectoryString, sepString, parentDirectoryString
-	].
-	^ '.'
+        "/ no separator found
+        p = '.' ifTrue:[
+            ^ parentDirectoryString
+        ].
+        p = '..' ifTrue:[
+            ^ parentDirectoryString, sepString, parentDirectoryString
+        ].
+        ^ '.'
     ].
     rest := p copyFrom:(index+1).
     (rest = '.') ifTrue:[
-	^ p copyTo:index-1.
+        ^ p copyTo:index-1.
     ].
     (rest = parentDirectoryString) ifTrue:[
-	^ (self species named:(p copyTo:(index-1))) directoryName
+        ^ (self species named:(p copyTo:(index-1))) directoryName
     ].
     index == 1 ifTrue:[
-	^ sepString
+        ^ sepString
     ].
     ^ p copyTo:(index - 1)
 
@@ -5034,7 +5039,7 @@
 
 directoryPathName
     "return the full directory pathname part of the file/directory as a string.
-     - thats the full pathname of the directory where the file/dir represented by
+     - that's the full pathname of the directory where the file/dir represented by
        the receiver is contained in.
      See also: #pathName, #directoryName, #directory and #baseName"
 
@@ -5296,7 +5301,7 @@
      '/foo/bar' asFilename isAbsolute
      '~/bla' asFilename isAbsolute
      '..' asFilename isAbsolute
-     '..' asAbsoluteFilename isAbsolute
+     '..' asFilename asAbsoluteFilename isAbsolute
      'source/SBrowser.st' asFilename isAbsolute
      'source/SBrowser.st' asFilename isRelative
      'SBrowser.st' asFilename isRelative
@@ -5495,7 +5500,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
+     If the receiver represents a symbolic link, that's the fileName of the
      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."
@@ -5504,7 +5509,7 @@
 
     pathOrNil := self physicalPathName.
     pathOrNil isNil ifTrue:[
-	^ nil
+        ^ nil
     ].
     ^ pathOrNil asFilename
 
@@ -5515,7 +5520,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
+     If the receiver represents a symbolic link, that's the fileName of the
      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."
@@ -5524,30 +5529,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
@@ -5579,7 +5584,7 @@
 
 tail:nComponents
     "return the last n components of myself.
-     - thats the file/directory name without leading parent-dirs.
+     - that's the file/directory name without leading parent-dirs.
      (i.e. '/usr/lib/st/file' asFilename tail:2 -> 'st/file'
        and '/usr/lib'         asFilename tail:1 -> lib).
      This method does not check if the path is valid.
@@ -5593,15 +5598,15 @@
     components := self components.
     start := components size - nComponents + 1.
     start < 1 ifTrue:[
-	start := 1.
+        start := 1.
     ].
     start = 1 ifTrue:[
-	tail := ''
+        tail := ''
     ] ifFalse:[
-	tail := components at:start.
+        tail := components at:start.
     ].
     start+1 to:components size do:[:i|
-	tail := tail, sep, (components at:i).
+        tail := tail, sep, (components at:i).
     ].
     ^ tail.
 
--- a/FixedPoint.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/FixedPoint.st	Mon Oct 03 12:44:41 2016 +0100
@@ -313,7 +313,6 @@
     "
 ! !
 
-
 !FixedPoint class methodsFor:'printing control'!
 
 printTruncated
@@ -339,7 +338,6 @@
     ^ $s
 ! !
 
-
 !FixedPoint methodsFor:'accessing'!
 
 scale
@@ -703,7 +701,7 @@
 !FixedPoint methodsFor:'coercing & converting'!
 
 asFixedPoint
-    "return the receiver as a fixedPoint number - thats the receiver itself"
+    "return the receiver as a fixedPoint number - that's the receiver itself"
 
     ^ self
 
@@ -1323,7 +1321,6 @@
     "Modified: 12.4.1997 / 11:22:02 / cg"
 ! !
 
-
 !FixedPoint methodsFor:'testing'!
 
 isFixedPoint
--- a/Float.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Float.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -496,7 +498,6 @@
     ^ Epsilon
 ! !
 
-
 !Float class methodsFor:'binary storage'!
 
 readBinaryIEEEDoubleFrom:aStream
@@ -778,7 +779,6 @@
     "
 ! !
 
-
 !Float class methodsFor:'queries'!
 
 exponentCharacter
@@ -833,7 +833,6 @@
     ^ 2 "must be careful here, whenever ST/X is used on VAX or a 370"
 ! !
 
-
 !Float methodsFor:'arithmetic'!
 
 * aNumber
@@ -2030,7 +2029,7 @@
      systems; on SYSV machines you have to give something like %lf,
      while on BSD systems the format string has to be %F.
      Also, the resulting string may not be longer than 255 bytes -
-     since thats the (static) size of the buffer.
+     since that's the (static) size of the buffer.
      This method is NONSTANDARD and may be removed without notice.
      WARNNG: this goes directly to the C-printf function and may therefore me inherently unsafe.
 
@@ -2042,23 +2041,23 @@
     int len;
 
     if (__isStringLike(formatString)) {
-	/*
-	 * actually only needed on sparc: since thisContext is
-	 * in a global register, which gets destroyed by printf,
-	 * manually save it here - very stupid ...
-	 */
-	__BEGIN_PROTECT_REGISTERS__
-
-	len = snprintf(buffer, sizeof(buffer), __stringVal(formatString), __floatVal(self));
-
-	__END_PROTECT_REGISTERS__
-
-	if (len < 0) goto fail;
-
-	s = __MKSTRING_L(buffer, len);
-	if (s != nil) {
-	    RETURN (s);
-	}
+        /*
+         * actually only needed on sparc: since thisContext is
+         * in a global register, which gets destroyed by printf,
+         * manually save it here - very stupid ...
+         */
+        __BEGIN_PROTECT_REGISTERS__
+
+        len = snprintf(buffer, sizeof(buffer), __stringVal(formatString), __floatVal(self));
+
+        __END_PROTECT_REGISTERS__
+
+        if (len < 0) goto fail;
+
+        s = __MKSTRING_L(buffer, len);
+        if (s != nil) {
+            RETURN (s);
+        }
     }
 fail: ;
 %}.
@@ -2347,7 +2346,6 @@
     "
 ! !
 
-
 !Float methodsFor:'testing'!
 
 isFinite
--- a/Fraction.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Fraction.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -589,7 +587,7 @@
 !
 
 asFraction
-    "return the receiver as fraction - thats itself"
+    "return the receiver as fraction - that's the receiver itself"
 
     ^ self
 !
--- a/GenericException.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/GenericException.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -1130,6 +1132,14 @@
     "Created: / 23.7.1999 / 13:49:59 / stefan"
 !
 
+isProgramError
+    "redefined in all exceptions which are programmer's errors,
+     and which should probably not be ignored.
+     I.e. a global error handler should reject and let a debugger get control."
+
+    ^ false
+!
+
 isQuerySignal
     "return true, if this is a querySignal - always return false here"
 
@@ -1357,7 +1367,7 @@
 
 originalSignal
     "return the signal/exception which was originally raised.
-     For noHandler, that is my unhandled signal; for others, thats the exception itself."
+     For noHandler, that is my unhandled signal; for others, that's the exception itself."
 
     ^ self.
 !
@@ -2425,6 +2435,14 @@
 
 isNotification
     ^ false
+!
+
+isProgramError
+    "redefined in all exceptions which are programmer's errors,
+     and which should probably not be ignored.
+     I.e. a global error handler should reject and let a debugger get control."
+     
+    ^ self class isProgramError
 ! !
 
 !GenericException class methodsFor:'documentation'!
--- a/IndexNotFoundError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/IndexNotFoundError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 NotFoundError subclass:#IndexNotFoundError
     instanceVariableNames: ''
     classVariableNames: ''
@@ -55,7 +57,7 @@
 !IndexNotFoundError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/IndexNotFoundError.st,v 1.4 2013-04-27 10:06:42 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/LargeInteger.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/LargeInteger.st	Mon Oct 03 12:44:41 2016 +0100
@@ -315,8 +315,6 @@
     "Modified: / 8.5.1998 / 21:40:41 / cg"
 ! !
 
-
-
 !LargeInteger class methodsFor:'queries'!
 
 isBuiltInClass
@@ -499,14 +497,14 @@
      The result is truncated toward negative infinity
      and will be negative, if the operands signs differ.
      The following is always true:
-        (receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
+	(receiver // aNumber) * aNumber + (receiver \\ aNumber) = receiver
 
      Be careful with negative results: 9 // 4 -> 2, while -9 // 4 -> -3.
      Especially surprising (because of truncation toward negative infinity):
-        -1 // 10 -> -1 (because -(1/10) is truncated towards next smaller integer, which is -1.
-        -10 // 3 -> -4 (because -(10/3) is truncated towards next smaller integer, which is -4.
-
-     See #quo: which truncates toward zero and returns -2 in the above case 
+	-1 // 10 -> -1 (because -(1/10) is truncated towards next smaller integer, which is -1.
+	-10 // 3 -> -4 (because -(10/3) is truncated towards next smaller integer, which is -4.
+
+     See #quo: which truncates toward zero and returns -2 in the above case
      and #rem: which is the corresponding remainder."
 
     |nrClass divMod quo|
@@ -518,19 +516,19 @@
      Use a special method for this case ...
     "
     ((nrClass == SmallInteger) or:[ nrClass == self class]) ifFalse:[
-        ^ self retry:#// coercing:aNumber
+	^ self retry:#// coercing:aNumber
     ].
     divMod := self absDivMod:aNumber.
 
     quo := divMod at:1.
     (sign == aNumber sign) ifFalse:[
-        "/ adjust for truncation if negative and there is a remainder ...
-        "/ be careful: there is one special case to care for here:
-        "/ if quo is maxInt+1, the negation can be represented as a smallInt.
-        quo := quo setSign:-1.
-        (divMod at:2) == 0 ifFalse:[
-            ^ quo - 1
-        ].
+	"/ adjust for truncation if negative and there is a remainder ...
+	"/ be careful: there is one special case to care for here:
+	"/ if quo is maxInt+1, the negation can be represented as a smallInt.
+	quo := quo setSign:-1.
+	(divMod at:2) == 0 ifFalse:[
+	    ^ quo - 1
+	].
 "/        quo digitLength == SmallInteger maxBytes ifTrue:[
 "/            ^ quo compressed
 "/        ].
@@ -799,7 +797,7 @@
      truncates toward negative infinity).
      The result's sign is negative if the receiver has a sign different from the arg's sign.
      The following is always true:
-        (receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
+	(receiver quo: aNumber) * aNumber + (receiver rem: aNumber) = receiver
      For positive results, this is the same as #//,
      for negative results, the remainder is ignored.
      I.e.: '9 // 4 = 2' and '-9 // 4 = -3'
@@ -809,12 +807,12 @@
 
     nrClass := aNumber class.
     ((nrClass == SmallInteger) or:[ nrClass == self class] ) ifFalse:[
-        ^ self retry:#quo: coercing:aNumber
+	^ self retry:#quo: coercing:aNumber
     ].
 
     quo := (self absDivMod:aNumber) at:1.
     (sign == aNumber sign) ifTrue:[
-        ^ quo
+	^ quo
     ].
     ^ quo setSign:-1
 
@@ -1676,7 +1674,7 @@
 !LargeInteger methodsFor:'coercing & converting'!
 
 asLargeInteger
-    "return a LargeInteger with same value as myself - thats me"
+    "return a LargeInteger with same value as myself - that's me"
 
     ^ self
 !
@@ -2338,60 +2336,60 @@
 
     num := anInteger abs.
     SmallInteger maxBytes == 8 ifTrue:[
-        (num > 16rFFFFFFFFFF) ifTrue:[
-            "if num is too big (so that multiplying by a byte could create a Large)"
-            ^ anInteger retry:#* coercing:self
-        ].
+	(num > 16rFFFFFFFFFF) ifTrue:[
+	    "if num is too big (so that multiplying by a byte could create a Large)"
+	    ^ anInteger retry:#* coercing:self
+	].
     ] ifFalse:[
-        (num > 16r3FFFFF) ifTrue:[
-            "if num is too big (so that multiplying by a byte could create a Large)"
-            ^ anInteger retry:#* coercing:self
-        ].
+	(num > 16r3FFFFF) ifTrue:[
+	    "if num is too big (so that multiplying by a byte could create a Large)"
+	    ^ anInteger retry:#* coercing:self
+	].
     ].
 
     len := digitByteArray size.
 
     val := num.
     val <= 16rFF ifTrue:[
-        lResult := len + 1.
+	lResult := len + 1.
     ] ifFalse:[
-        val <= 16rFFFF ifTrue:[
-            lResult := len + 2
-        ] ifFalse:[
-            val <= 16rFFFFFF ifTrue:[
-                lResult := len + 4.
-            ] ifFalse:[
-                val <= 16rFFFFFFFF ifTrue:[
-                    lResult := len + 6.
-                ] ifFalse:[
-                    val <= 16rFFFFFFFFFF ifTrue:[
-                        lResult := len + 8.
-                    ] ifFalse:[
-                        val <= 16rFFFFFFFFFF ifTrue:[
-                            lResult := len + 10.
-                        ] ifFalse:[
-                            val <= 16rFFFFFFFFFFFF ifTrue:[
-                                lResult := len + 12.
-                            ] ifFalse:[
-                                lResult := len + 14.
-                            ]
-                        ]
-                    ]
-                ]
-            ]
-        ]
+	val <= 16rFFFF ifTrue:[
+	    lResult := len + 2
+	] ifFalse:[
+	    val <= 16rFFFFFF ifTrue:[
+		lResult := len + 4.
+	    ] ifFalse:[
+		val <= 16rFFFFFFFF ifTrue:[
+		    lResult := len + 6.
+		] ifFalse:[
+		    val <= 16rFFFFFFFFFF ifTrue:[
+			lResult := len + 8.
+		    ] ifFalse:[
+			val <= 16rFFFFFFFFFF ifTrue:[
+			    lResult := len + 10.
+			] ifFalse:[
+			    val <= 16rFFFFFFFFFFFF ifTrue:[
+				lResult := len + 12.
+			    ] ifFalse:[
+				lResult := len + 14.
+			    ]
+			]
+		    ]
+		]
+	    ]
+	]
     ].
     resultDigitByteArray := ByteArray uninitializedNew:lResult.
     result := self class basicNew setDigits:resultDigitByteArray.
 
     anInteger < 0 ifTrue:[
-        sign > 0 ifTrue:[
-            result setSign:-1
-        ].
+	sign > 0 ifTrue:[
+	    result setSign:-1
+	].
     ] ifFalse:[
-        sign < 0 ifTrue:[
-            result setSign:sign
-        ]
+	sign < 0 ifTrue:[
+	    result setSign:sign
+	]
     ].
 
     ok := false.
@@ -2401,194 +2399,252 @@
     if (__isSmallInteger(len)
      && __isByteArray(__digitByteArray)
      && __isByteArray(resultDigitByteArray)) {
-        INT _l = __intVal(len);
-        INT _v = __intVal(val);
-        unsigned INT _carry = 0;
-        unsigned INT _prod;
-        unsigned char *digitP = __ByteArrayInstPtr(__digitByteArray)->ba_element;
-        unsigned char *resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
-
-        /*
-         * skipping zeros does not help much (a few percent) on
-         * a P5 or other CPUS with a fast multiplier.
-         * It may make more of a difference on CPUs with slower 0-multiply.
-         * Late news: it actually hurts modern x86_64 cpus.
-         * So only reenable for specific CPUs after concrete benchmarks.
-         */
+	INT _l = __intVal(len);
+	INT _v = __intVal(val);
+	unsigned INT _carry = 0;
+	unsigned INT _prod;
+	unsigned char *digitP = __ByteArrayInstPtr(__digitByteArray)->ba_element;
+	unsigned char *resultP = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
+
+	/*
+	 * skipping zeros does not help much (a few percent) on
+	 * a P5 or other CPUS with a fast multiplier.
+	 * It may make more of a difference on CPUs with slower 0-multiply.
+	 * Late news: it actually hurts modern x86_64 cpus.
+	 * So only reenable for specific CPUs after concrete benchmarks.
+	 */
 #if 0
-        while ((_l >= sizeof(INT)) && (((unsigned INT *)digitP)[0] == 0)) {
-            ((unsigned INT *)resultP)[0] = 0;
-            digitP += sizeof(INT);
-            resultP += sizeof(INT);
-            _l -= sizeof(INT);
-        }
+	while ((_l >= sizeof(INT)) && (((unsigned INT *)digitP)[0] == 0)) {
+	    ((unsigned INT *)resultP)[0] = 0;
+	    digitP += sizeof(INT);
+	    resultP += sizeof(INT);
+	    _l -= sizeof(INT);
+	}
 #endif
 
 #if defined(__LSBFIRST__)
 # if defined (__GNUC__) && defined(__i386__) && (__POINTER_SIZE__ == 4)
-        /*
-         * can do it long-word-wise;
-         * 32*32 -> 64 multiplication
-         */
-        while (_l > 3) {
-            unsigned __pHi, __pLow;
-            unsigned __digit;
-
-            /*
-             * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
-             * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
-             */
-            __digit = ((unsigned long *)digitP)[0];
-            asm ("mull %3               \n\
-                  addl %4,%%eax         \n\
-                  adcl $0,%%edx"
-                    : "=a"  (__pLow),
-                      "=d"  (__pHi)
-                    : "0"   (__digit),
-                      "1"   (ASM_ULONGCAST(_v)),
-                      "rm"  (ASM_ULONGCAST(_carry)) );
-
-            ((unsigned long *)resultP)[0] = __pLow;
-            _carry = __pHi;
-            digitP += 4;
-            resultP += 4;
-            _l -= 4;
-        }
+	/*
+	 * can do it long-word-wise;
+	 * 32*32 -> 64 multiplication
+	 */
+	while (_l > 3) {
+	    unsigned __pHi, __pLow;
+	    unsigned __digit;
+
+	    /*
+	     * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
+	     * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
+	     */
+	    __digit = ((unsigned long *)digitP)[0];
+	    asm ("mull %3               \n\
+		  addl %4,%%eax         \n\
+		  adcl $0,%%edx"
+		    : "=a"  (__pLow),
+		      "=d"  (__pHi)
+		    : "0"   (__digit),
+		      "1"   (ASM_ULONGCAST(_v)),
+		      "rm"  (ASM_ULONGCAST(_carry)) );
+
+	    ((unsigned long *)resultP)[0] = __pLow;
+	    _carry = __pHi;
+	    digitP += 4;
+	    resultP += 4;
+	    _l -= 4;
+	}
 # else /* not GNU-i386 */
 #  if defined(__win32__) && defined(__BORLANDC__) && defined(__x86__) && (__POINTER_SIZE__ == 4)
-        /*
-         * can do it long-word-wise;
-         * 32*32 -> 64 multiplication
-         */
-        while (_l > 3) {
-            unsigned __pLow;
-            unsigned digit;
-
-            /*
-             * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
-             * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
-             */
+	/*
+	 * can do it long-word-wise;
+	 * 32*32 -> 64 multiplication
+	 */
+	while (_l > 3) {
+	    unsigned __pLow;
+	    unsigned digit;
+
+	    /*
+	     * max: 0xFFFF.FFFF * 0xFFFF.FFFF -> 0xFFFF.FFFE.0000.0001
+	     * + maxCarry (0xFFFF.FFFF)  -> 0xFFFF.FFFF.0000.0000
+	     */
 /*
-            digit = ((unsigned long *)digitP)[0];
-            edx::eax = (digit * _v);
-            edx::eax += _carry;
-            ((unsigned long *)resultP)[0] = eax; -- pLow
-            _carry = edx; -- pHigh
-            digitP += 4;
-            resultP += 4;
+	    digit = ((unsigned long *)digitP)[0];
+	    edx::eax = (digit * _v);
+	    edx::eax += _carry;
+	    ((unsigned long *)resultP)[0] = eax; -- pLow
+	    _carry = edx; -- pHigh
+	    digitP += 4;
+	    resultP += 4;
 */
-            digit = ((unsigned long *)digitP)[0];
-            asm {
-                mov   eax, digit
-                mov   edx, _v
-                mul   edx
-                add   eax, _carry
-                adc   edx, 0
-                mov   __pLow, eax
-                mov   _carry, edx
-            }
-
-            ((unsigned long *)resultP)[0] = __pLow;
-            digitP += 4;
-            resultP += 4;
-            _l -= 4;
-        }
+	    digit = ((unsigned long *)digitP)[0];
+	    asm {
+		mov   eax, digit
+		mov   edx, _v
+		mul   edx
+		add   eax, _carry
+		adc   edx, 0
+		mov   __pLow, eax
+		mov   _carry, edx
+	    }
+
+	    ((unsigned long *)resultP)[0] = __pLow;
+	    digitP += 4;
+	    resultP += 4;
+	    _l -= 4;
+	}
 #  else /* not WIN32-i386 */
+#   if defined(INT128)
+	if (_v <= 0xFFFFFFFFFFFFFFFFL) {
+	    /* have 128bit ints; can do it int64-wise
+	     *
+	     */
+	    while (_l >= 8) {
+		UINT64 __t1;
+		UINT128 _prod128a;
+
+		__t1 = ((UINT64 *)digitP)[0];
+		_prod128a = (INT128)_v;
+		_prod128a *= __t1;
+		_prod128a += _carry;
+		((UINT64 *)resultP)[0] = _prod128a;
+		_carry = _prod128a >> 64;
+
+		digitP += (8);
+		resultP += (8);
+		_l -= (8);
+	    }
+	    while (_l >= 4) {
+		unsigned __t;
+		UINT128 _prod128;
+
+		__t = ((unsigned *)digitP)[0];
+		_prod128 = (INT128)_v;
+		_prod128 *= __t;
+		_prod128 += _carry;
+		((unsigned *)resultP)[0] = _prod128 /* & 0xFFFFFFFFL */;
+		_carry = _prod128 >> 32;
+		digitP += 4;
+		resultP += 4;
+		_l -= 4;
+	    }
+	    if (_l >= 2) {
+		unsigned short __t;
+		UINT128 _prod128;
+
+		__t = ((unsigned short *)digitP)[0];
+		_prod128 = (INT128)_v;
+		_prod128 *= __t;
+		_prod128 += _carry;
+		((unsigned short *)resultP)[0] = _prod128 /* & 0xFFFF */;
+		_carry = _prod128 >> 16;
+		digitP += 2;
+		resultP += 2;
+		_l -= 2;
+	    }
+	    if (_l > 0) {
+		UINT128 _prod128;
+		_prod128 = *digitP++ * _v + _carry;
+		*resultP++ = _prod128 /* & 0xFF */;
+		_carry = _prod128 >> 8;
+		_l--;
+	    }
+	}
+#   endif
+
 #   if defined(INT64)
-        if (_v <= 0xFFFFFFFFL) {
-            /* have 64bit ints; can do it int-wise
-             *
-             * max: 0xFFFFFFFF * 0xFFFFFFFF -> 0xFFFFFFFE.0001
-             * + maxCarry (0xFFFFFFFF)  -> 0xFFFFFFFF.0000
-             */
-            while (_l >= (4+4+4+4)) {
-                unsigned __t1, __t2, __t3, __t4;
-                UINT64 _prod64a, _prod64b, _prod64c, _prod64d;
-
-                __t1 = ((unsigned *)digitP)[0];
-                _prod64a = (INT64)_v;
-                _prod64a *= __t1;
-                _prod64a += _carry;
-                ((unsigned *)resultP)[0] = _prod64a /* & 0xFFFFFFFFL */;
-                _carry = _prod64a >> 32;
-
-                __t2 = ((unsigned *)digitP)[1];
-                _prod64b = (INT64)_v;
-                _prod64b *= __t2;
-                _prod64b += _carry;
-                ((unsigned *)resultP)[1] = _prod64b /* & 0xFFFFFFFFL */;
-                _carry = _prod64b >> 32;
-
-                __t3 = ((unsigned *)digitP)[2];
-                _prod64c = (INT64)_v;
-                _prod64c *= __t3;
-                _prod64c += _carry;
-                ((unsigned *)resultP)[2] = _prod64c /* & 0xFFFFFFFFL */;
-                _carry = _prod64c >> 32;
-
-                __t4 = ((unsigned *)digitP)[3];
-                _prod64d = (INT64)_v;
-                _prod64d *= __t4;
-                _prod64d += _carry;
-                ((unsigned *)resultP)[3] = _prod64d /* & 0xFFFFFFFFL */;
-                _carry = _prod64d >> 32;
-
-                digitP += (4+4+4+4);
-                resultP += (4+4+4+4);
-                _l -= (4+4+4+4);
-            }
-            while (_l >= 4) {
-                unsigned __t;
-                UINT64 _prod64;
-
-                __t = ((unsigned *)digitP)[0];
-                _prod64 = (INT64)_v;
-                _prod64 *= __t;
-                _prod64 += _carry;
-                ((unsigned *)resultP)[0] = _prod64 /* & 0xFFFFFFFFL */;
-                _carry = _prod64 >> 32;
-                digitP += 4;
-                resultP += 4;
-                _l -= 4;
-            }
-            if (_l >= 2) {
-                unsigned short __t;
-                UINT64 _prod64;
-
-                __t = ((unsigned short *)digitP)[0];
-                _prod64 = (INT64)_v;
-                _prod64 *= __t;
-                _prod64 += _carry;
-                ((unsigned short *)resultP)[0] = _prod64 /* & 0xFFFF */;
-                _carry = _prod64 >> 16;
-                digitP += 2;
-                resultP += 2;
-                _l -= 2;
-            }
-            if (_l > 0) {
-                UINT64 _prod64;
-                _prod64 = *digitP++ * _v + _carry;
-                *resultP++ = _prod64 /* & 0xFF */;
-                _carry = _prod64 >> 8;
-                _l--;
-            }
-        }
+	if (_v <= 0xFFFFFFFFL) {
+	    /* have 64bit ints; can do it int-wise
+	     *
+	     * max: 0xFFFFFFFF * 0xFFFFFFFF -> 0xFFFFFFFE.0001
+	     * + maxCarry (0xFFFFFFFF)  -> 0xFFFFFFFF.0000
+	     */
+	    while (_l >= (4+4+4+4)) {
+		unsigned __t1, __t2, __t3, __t4;
+		UINT64 _prod64a, _prod64b, _prod64c, _prod64d;
+
+		__t1 = ((unsigned *)digitP)[0];
+		_prod64a = (INT64)_v;
+		_prod64a *= __t1;
+		_prod64a += _carry;
+		((unsigned *)resultP)[0] = _prod64a /* & 0xFFFFFFFFL */;
+		_carry = _prod64a >> 32;
+
+		__t2 = ((unsigned *)digitP)[1];
+		_prod64b = (INT64)_v;
+		_prod64b *= __t2;
+		_prod64b += _carry;
+		((unsigned *)resultP)[1] = _prod64b /* & 0xFFFFFFFFL */;
+		_carry = _prod64b >> 32;
+
+		__t3 = ((unsigned *)digitP)[2];
+		_prod64c = (INT64)_v;
+		_prod64c *= __t3;
+		_prod64c += _carry;
+		((unsigned *)resultP)[2] = _prod64c /* & 0xFFFFFFFFL */;
+		_carry = _prod64c >> 32;
+
+		__t4 = ((unsigned *)digitP)[3];
+		_prod64d = (INT64)_v;
+		_prod64d *= __t4;
+		_prod64d += _carry;
+		((unsigned *)resultP)[3] = _prod64d /* & 0xFFFFFFFFL */;
+		_carry = _prod64d >> 32;
+
+		digitP += (4+4+4+4);
+		resultP += (4+4+4+4);
+		_l -= (4+4+4+4);
+	    }
+	    while (_l >= 4) {
+		unsigned __t;
+		UINT64 _prod64;
+
+		__t = ((unsigned *)digitP)[0];
+		_prod64 = (INT64)_v;
+		_prod64 *= __t;
+		_prod64 += _carry;
+		((unsigned *)resultP)[0] = _prod64 /* & 0xFFFFFFFFL */;
+		_carry = _prod64 >> 32;
+		digitP += 4;
+		resultP += 4;
+		_l -= 4;
+	    }
+	    if (_l >= 2) {
+		unsigned short __t;
+		UINT64 _prod64;
+
+		__t = ((unsigned short *)digitP)[0];
+		_prod64 = (INT64)_v;
+		_prod64 *= __t;
+		_prod64 += _carry;
+		((unsigned short *)resultP)[0] = _prod64 /* & 0xFFFF */;
+		_carry = _prod64 >> 16;
+		digitP += 2;
+		resultP += 2;
+		_l -= 2;
+	    }
+	    if (_l > 0) {
+		UINT64 _prod64;
+		_prod64 = *digitP++ * _v + _carry;
+		*resultP++ = _prod64 /* & 0xFF */;
+		_carry = _prod64 >> 8;
+		_l--;
+	    }
+	}
 #   else /* no INT64 type */
-        if (_v <= 0xFFFF) {
-            /* can do it short-wise
-             *
-             * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
-             * + maxCarry (0xFFFF)  -> 0xFFFF.0000
-             */
-            while (_l > 1) {
-                _prod = ((unsigned short *)digitP)[0] * _v + _carry;
-                ((unsigned short *)resultP)[0] = _prod /* & 0xFFFF */;
-                _carry = _prod >> 16;
-                digitP += 2;
-                resultP += 2;
-                _l -= 2;
-            }
-        }
+	if (_v <= 0xFFFF) {
+	    /* can do it short-wise
+	     *
+	     * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
+	     * + maxCarry (0xFFFF)  -> 0xFFFF.0000
+	     */
+	    while (_l > 1) {
+		_prod = ((unsigned short *)digitP)[0] * _v + _carry;
+		((unsigned short *)resultP)[0] = _prod /* & 0xFFFF */;
+		_carry = _prod >> 16;
+		digitP += 2;
+		resultP += 2;
+		_l -= 2;
+	    }
+	}
 #   endif /* no INT64 */
 #  endif /* not WIN32-i386 */
 # endif /* not GNU-i386 */
@@ -2599,80 +2655,80 @@
    /* no, STORE_WORD_WISE makes it slower */
 # endif
 
-        if (_v <= 0xFFFF) {
-            /* can do it short-wise
-             *
-             * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
-             * + maxCarry (0xFFFF)  -> 0xFFFF.0000
-             */
-            while (_l > 1) {
-                unsigned int t;
+	if (_v <= 0xFFFF) {
+	    /* can do it short-wise
+	     *
+	     * max: 0xFFFF * 0xFFFF -> 0xFFFE.0001
+	     * + maxCarry (0xFFFF)  -> 0xFFFF.0000
+	     */
+	    while (_l > 1) {
+		unsigned int t;
 
 #if defined(LOAD_WORD_WISE)
-                /* better fetch short-wise */
-                t = ((unsigned short *)digitP)[0];
-                digitP += 2;
-                t = ((t >> 8) | (t << 8)) & 0xFFFF;
+		/* better fetch short-wise */
+		t = ((unsigned short *)digitP)[0];
+		digitP += 2;
+		t = ((t >> 8) | (t << 8)) & 0xFFFF;
 #else
-                t = (digitP[1]<<8) + digitP[0];
-                digitP += 2;
+		t = (digitP[1]<<8) + digitP[0];
+		digitP += 2;
 #endif
-                _prod = t * _v + _carry;
-                _carry = _prod >> 16;
+		_prod = t * _v + _carry;
+		_carry = _prod >> 16;
 #if defined(STORE_WORD_WISE)
-                /* better store short-wise */
-                _prod = ((_prod >> 8) | (_prod << 8)) & 0xFFFF;
-                ((unsigned short *)resultP)[0] = _prod;
+		/* better store short-wise */
+		_prod = ((_prod >> 8) | (_prod << 8)) & 0xFFFF;
+		((unsigned short *)resultP)[0] = _prod;
 #else
-                resultP[0] = _prod /* & 0xFF */;
-                resultP[1] = (_prod>>8) /* & 0xFF */;
+		resultP[0] = _prod /* & 0xFF */;
+		resultP[1] = (_prod>>8) /* & 0xFF */;
 #endif
-                resultP += 2;
-                _l -= 2;
-            }
-        }
+		resultP += 2;
+		_l -= 2;
+	    }
+	}
 
 #endif /* LSB_FIRST */
 
-        /*
-         * rest is done byte-wise
-         */
-        while (_l > 0) {
-            _prod = *digitP++ * _v + _carry;
-            *resultP++ = _prod /* & 0xFF */;
-            _carry = _prod >> 8;
-            _l--;
-        }
-
-        _l = __intVal(lResult) - __intVal(len);
-
-        /*
-         * remaining carry
-         */
-        while (_carry) {
-            *resultP++ = _carry /* & 0xFF */;
-            _carry >>= 8;
-            _l--;
-        }
-
-        /*
-         * remaining zeros
-         */
-        while (_l--) {
-            *resultP++ = 0;
-        }
-
-        /*
-         * need compress ?
-         */
-        if (resultP[-1]) {
-            /*
-             * no
-             */
-            RETURN(result);
-        }
-
-        ok = true;
+	/*
+	 * rest is done byte-wise
+	 */
+	while (_l > 0) {
+	    _prod = *digitP++ * _v + _carry;
+	    *resultP++ = _prod /* & 0xFF */;
+	    _carry = _prod >> 8;
+	    _l--;
+	}
+
+	_l = __intVal(lResult) - __intVal(len);
+
+	/*
+	 * remaining carry
+	 */
+	while (_carry) {
+	    *resultP++ = _carry /* & 0xFF */;
+	    _carry >>= 8;
+	    _l--;
+	}
+
+	/*
+	 * remaining zeros
+	 */
+	while (_l--) {
+	    *resultP++ = 0;
+	}
+
+	/*
+	 * need compress ?
+	 */
+	if (resultP[-1]) {
+	    /*
+	     * no
+	     */
+	    RETURN(result);
+	}
+
+	ok = true;
     }
 %}.
     "
@@ -2680,21 +2736,21 @@
      (could make it a primitive-failure as well)
     "
     ok ifFalse:[
-        carry := 0.
-        1 to:len do:[:i |
-            prod := (digitByteArray basicAt:i) * val + carry.
-            resultDigitByteArray basicAt:i put:(prod bitAnd:16rFF).
-            carry := prod bitShift:-8.
-        ].
-        [carry ~~ 0] whileTrue:[
-            len := len + 1.
-            resultDigitByteArray basicAt:len put:(carry bitAnd:16rFF).
-            carry := carry bitShift:-8
-        ].
-        [len < lResult] whileTrue:[
-            len := len + 1.
-            resultDigitByteArray basicAt:len put:0
-        ]
+	carry := 0.
+	1 to:len do:[:i |
+	    prod := (digitByteArray basicAt:i) * val + carry.
+	    resultDigitByteArray basicAt:i put:(prod bitAnd:16rFF).
+	    carry := prod bitShift:-8.
+	].
+	[carry ~~ 0] whileTrue:[
+	    len := len + 1.
+	    resultDigitByteArray basicAt:len put:(carry bitAnd:16rFF).
+	    carry := carry bitShift:-8
+	].
+	[len < lResult] whileTrue:[
+	    len := len + 1.
+	    resultDigitByteArray basicAt:len put:0
+	]
     ].
     ^ result compressed
 !
@@ -3506,7 +3562,7 @@
 
     ((aSmallInteger < (SmallInteger minVal + 255))
     or:[aSmallInteger > (SmallInteger maxVal - 255)]) ifTrue:[
-        ^ self absPlus:(self class value:aSmallInteger) sign:newSign.
+	^ self absPlus:(self class value:aSmallInteger) sign:newSign.
     ].
 
     len := rsltLen := digitByteArray size.
@@ -3515,18 +3571,18 @@
     "/ if it is 255 (since the other number is definitely smaller)
     "/
     (digitByteArray at:len) == 16rFF ifTrue:[
-        rsltLen := len + 1.
+	rsltLen := len + 1.
     ] ifFalse:[
-        "/ or the argument has something in the high byte ..
+	"/ or the argument has something in the high byte ..
 %{
 #if __POINTER_SIZE__ == 8
-        if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
-            rsltLen = __mkSmallInteger(__intVal(len) + 1);
-        }
+	if (__intVal(aSmallInteger) & 0xFF00000000000000L) {
+	    rsltLen = __mkSmallInteger(__intVal(len) + 1);
+	}
 #else
-        if (__intVal(aSmallInteger) & 0xFF000000) {
-            rsltLen = __mkSmallInteger(__intVal(len) + 1);
-        }
+	if (__intVal(aSmallInteger) & 0xFF000000) {
+	    rsltLen = __mkSmallInteger(__intVal(len) + 1);
+	}
 #endif
 %}
     ].
@@ -3538,309 +3594,309 @@
     if (__isByteArray(__INST(digitByteArray))
      && __isByteArray(resultDigitByteArray)
      && __isSmallInteger(aSmallInteger)) {
-        /* carry is NOT unsigned (see negation below) */
-        INT __carry = __intVal(aSmallInteger);
-        int __index = 1;
-        int __len = __intVal(len);
-        unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
-        unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
-        INT __ptrDelta = __dst - __src;
-        unsigned char *__srcLast = __src + __len - 1;
-        int __rsltLen = __intVal(rsltLen);
-
-        if (__carry < 0) {
-            __carry = -__carry;
-        }
+	/* carry is NOT unsigned (see negation below) */
+	INT __carry = __intVal(aSmallInteger);
+	int __index = 1;
+	int __len = __intVal(len);
+	unsigned char *__src = (unsigned char *)(__ByteArrayInstPtr(__INST(digitByteArray))->ba_element);
+	unsigned char *__dst = (unsigned char *)(__ByteArrayInstPtr(resultDigitByteArray)->ba_element);
+	INT __ptrDelta = __dst - __src;
+	unsigned char *__srcLast = __src + __len - 1;
+	int __rsltLen = __intVal(rsltLen);
+
+	if (__carry < 0) {
+	    __carry = -__carry;
+	}
 
 #if defined(__LSBFIRST__)
 # if defined(__i386__) && defined(__GNUC__) && (__POINTER_SIZE__ == 4)
 #  if 0 /* NOTICE - the code below is 20% slower ... - why */
-        /*
-         * add long-wise
-         */
-        asm("  jecxz nothingToDo                                      \n\
-               movl  %%eax, %%esi      /* __src input */              \n\
-               movl  %%ebx, %%edi      /* __dst input */              \n\
-                                                                      \n\
-               /* the first 4-byte int */                             \n\
-               lodsl                   /* fetch */                    \n\
-               addl  %%edx, %%eax      /* add */                      \n\
-               stosl                   /* store */                    \n\
-               leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
-               jecxz doneLoop          /* any more ? */               \n\
-               /* remaining 4-byte ints */                            \n\
-               jmp   addLoop                                          \n\
-                                                                      \n\
-               .align 8                                               \n\
-             addLoop:                                                 \n\
-               movl  0(%%esi), %%ebx   /* fetch  */                   \n\
-               jnc   copyLoop2                                        \n\
-               movl  $0, %%eax                                        \n\
-               leal  4(%%esi), %%esi                                  \n\
-               adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
-               leal  8(%%edi), %%edi                                  \n\
-               movl  %%eax, -8(%%edi)  /* store */                    \n\
-               leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
-               jecxz doneLoop          /* any more ? */               \n\
-                                                                      \n\
-               movl  0(%%esi), %%ebx   /* fetch  */                   \n\
-               movl  $0, %%eax                                        \n\
-               leal  4(%%esi), %%esi                                  \
-               adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
-               movl  %%eax, -4(%%edi)  /* store */                    \n\
-                                                                      \n\
-               loop  addLoop                                          \n\
-               jmp   doneLoop                                         \n\
-                                                                      \n\
-               .align 8                                               \n\
-             copyLoop:                                                \n\
-               movl  0(%%esi), %%ebx                                  \n\
-             copyLoop2:                                               \n\
-               add   $4, %%esi                                        \n\
-               add   $4, %%edi                                        \n\
-               movl  %%ebx, -4(%%edi)                                 \n\
-               loop  copyLoop                                         \n\
-                                                                      \n\
-             doneLoop:                                                \n\
-               movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
-               adcl  $0, %%edx                                        \n\
-               movl  %%esi, %%eax      /* __src output */             \n\
-             nothingToDo:                                             \n\
-            " : "=d"  (ASM_ULONGCAST(__carry)),
-                "=a"  (__src)
-              : "1"   (__src),
-                "b"   (__dst),
-                "c"   (__len / 4),
-                "0"   (__carry)
-              : "esi", "edi");
+	/*
+	 * add long-wise
+	 */
+	asm("  jecxz nothingToDo                                      \n\
+	       movl  %%eax, %%esi      /* __src input */              \n\
+	       movl  %%ebx, %%edi      /* __dst input */              \n\
+								      \n\
+	       /* the first 4-byte int */                             \n\
+	       lodsl                   /* fetch */                    \n\
+	       addl  %%edx, %%eax      /* add */                      \n\
+	       stosl                   /* store */                    \n\
+	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
+	       jecxz doneLoop          /* any more ? */               \n\
+	       /* remaining 4-byte ints */                            \n\
+	       jmp   addLoop                                          \n\
+								      \n\
+	       .align 8                                               \n\
+	     addLoop:                                                 \n\
+	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
+	       jnc   copyLoop2                                        \n\
+	       movl  $0, %%eax                                        \n\
+	       leal  4(%%esi), %%esi                                  \n\
+	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
+	       leal  8(%%edi), %%edi                                  \n\
+	       movl  %%eax, -8(%%edi)  /* store */                    \n\
+	       leal  -1(%%ecx),%%ecx   /* do not clobber carry */     \n\
+	       jecxz doneLoop          /* any more ? */               \n\
+								      \n\
+	       movl  0(%%esi), %%ebx   /* fetch  */                   \n\
+	       movl  $0, %%eax                                        \n\
+	       leal  4(%%esi), %%esi                                  \
+	       adcl  %%ebx, %%eax      /* & add carry from prev int */\n\
+	       movl  %%eax, -4(%%edi)  /* store */                    \n\
+								      \n\
+	       loop  addLoop                                          \n\
+	       jmp   doneLoop                                         \n\
+								      \n\
+	       .align 8                                               \n\
+	     copyLoop:                                                \n\
+	       movl  0(%%esi), %%ebx                                  \n\
+	     copyLoop2:                                               \n\
+	       add   $4, %%esi                                        \n\
+	       add   $4, %%edi                                        \n\
+	       movl  %%ebx, -4(%%edi)                                 \n\
+	       loop  copyLoop                                         \n\
+								      \n\
+	     doneLoop:                                                \n\
+	       movl  $0, %%edx         /* do not clobber carry (xorl clears it) */   \n\
+	       adcl  $0, %%edx                                        \n\
+	       movl  %%esi, %%eax      /* __src output */             \n\
+	     nothingToDo:                                             \n\
+	    " : "=d"  (ASM_ULONGCAST(__carry)),
+		"=a"  (__src)
+	      : "1"   (__src),
+		"b"   (__dst),
+		"c"   (__len / 4),
+		"0"   (__carry)
+	      : "esi", "edi");
 
 #  else
-        {
-            unsigned char *__srcLastX;
-
-            __srcLastX = __srcLast - 3 - 4;
-            while (__src <= __srcLastX) {
-                unsigned int __sum, __sum2;
-                unsigned __digit1, __digit2;
-
-                __digit1 = ((unsigned *)__src)[0];
-                __digit2 = ((unsigned *)__src)[1];
-                asm ("addl %%edx,%%ecx          \n\
-                      adcl $0, %%eax            \n\
-                      movl $0, %%edx            \n\
-                      adcl $0, %%edx"
-                        : "=d"  (ASM_ULONGCAST(__carry)),
-                          "=c"  (ASM_ULONGCAST(__sum)),
-                          "=a"  (ASM_ULONGCAST(__sum2))
-                        : "0"   (ASM_ULONGCAST(__carry)),
-                          "1"   (__digit1),
-                          "2"   (__digit2));
-
-                ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
-                ((unsigned int *)(__src + __ptrDelta))[1] = __sum2;
-
-                __src += 8;
-
-                if (__carry == 0) {
-                    while (__src <= __srcLastX) {
-                        /* copy over words */
-                        ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
-                        ((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
-                        __src += 8;
-                    }
-                    while (__src <= __srcLast) {
-                        /* copy over bytes */
-                        __src[__ptrDelta] = __src[0];
-                        __src ++;
-                    }
-                    goto doneSource;
-                }
-            }
-
-            __srcLastX = __srcLastX + 4;
-            if (__src <= __srcLastX) {
-                unsigned int __sum, __digit;
-
-                __digit = ((unsigned *)__src)[0];
-
-                asm ("addl %%eax,%%edx  \n\
-                      movl $0,%%eax     \n\
-                      adcl $0,%%eax"
-                        : "=a"  (ASM_ULONGCAST(__carry)),
-                          "=d"  (ASM_ULONGCAST(__sum))
-                        : "0"   (ASM_ULONGCAST(__carry)),
-                          "1"   (__digit) );
-
-                ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
-                __src += 4;
-
-                if (__carry == 0) {
-                    while (__src <= __srcLast) {
-                        /* copy over bytes */
-                        __src[__ptrDelta] = __src[0];
-                        __src ++;
-                    }
-                    goto doneSource;
-                }
-            }
-        }
+	{
+	    unsigned char *__srcLastX;
+
+	    __srcLastX = __srcLast - 3 - 4;
+	    while (__src <= __srcLastX) {
+		unsigned int __sum, __sum2;
+		unsigned __digit1, __digit2;
+
+		__digit1 = ((unsigned *)__src)[0];
+		__digit2 = ((unsigned *)__src)[1];
+		asm ("addl %%edx,%%ecx          \n\
+		      adcl $0, %%eax            \n\
+		      movl $0, %%edx            \n\
+		      adcl $0, %%edx"
+			: "=d"  (ASM_ULONGCAST(__carry)),
+			  "=c"  (ASM_ULONGCAST(__sum)),
+			  "=a"  (ASM_ULONGCAST(__sum2))
+			: "0"   (ASM_ULONGCAST(__carry)),
+			  "1"   (__digit1),
+			  "2"   (__digit2));
+
+		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
+		((unsigned int *)(__src + __ptrDelta))[1] = __sum2;
+
+		__src += 8;
+
+		if (__carry == 0) {
+		    while (__src <= __srcLastX) {
+			/* copy over words */
+			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
+			((unsigned int *)(__src + __ptrDelta))[1] = ((unsigned int *)__src)[1];
+			__src += 8;
+		    }
+		    while (__src <= __srcLast) {
+			/* copy over bytes */
+			__src[__ptrDelta] = __src[0];
+			__src ++;
+		    }
+		    goto doneSource;
+		}
+	    }
+
+	    __srcLastX = __srcLastX + 4;
+	    if (__src <= __srcLastX) {
+		unsigned int __sum, __digit;
+
+		__digit = ((unsigned *)__src)[0];
+
+		asm ("addl %%eax,%%edx  \n\
+		      movl $0,%%eax     \n\
+		      adcl $0,%%eax"
+			: "=a"  (ASM_ULONGCAST(__carry)),
+			  "=d"  (ASM_ULONGCAST(__sum))
+			: "0"   (ASM_ULONGCAST(__carry)),
+			  "1"   (__digit) );
+
+		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
+		__src += 4;
+
+		if (__carry == 0) {
+		    while (__src <= __srcLast) {
+			/* copy over bytes */
+			__src[__ptrDelta] = __src[0];
+			__src ++;
+		    }
+		    goto doneSource;
+		}
+	    }
+	}
 #  endif
 # else /* not i386-GNUC */
 #  if defined(__win32__) && defined(__BORLANDC__) && defined(__x86__) && (__POINTER_SIZE__ == 4)
-        {
-            unsigned char *__srcLast4;
-
-            /*
-             * add long-wise
-             */
-            __srcLast4 = __srcLast - 3;
-            while (__src <= __srcLast4) {
-                unsigned int __sum;
-
-                __sum = ((unsigned int *)__src)[0];
-                asm {
-                      mov eax, __sum
-                      add eax, __carry
-                      mov edx, 0
-                      adc edx, 0
-                      mov __sum, eax
-                      mov __carry, edx
-                    }
-
-                ((unsigned int *)(__src + __ptrDelta))[0] = __sum;
-                __src += 4;
-                if (__carry == 0) {
-                    while (__src <= __srcLast4) {
-                        /* copy over words */
-                        ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
-                        __src += 4;
-                    }
-                    while (__src <= __srcLast) {
-                        /* copy over bytes */
-                        __src[__ptrDelta] = __src[0];
-                        __src ++;
-                    }
-                    goto doneSource;
-                }
-            }
-        }
+	{
+	    unsigned char *__srcLast4;
+
+	    /*
+	     * add long-wise
+	     */
+	    __srcLast4 = __srcLast - 3;
+	    while (__src <= __srcLast4) {
+		unsigned int __sum;
+
+		__sum = ((unsigned int *)__src)[0];
+		asm {
+		      mov eax, __sum
+		      add eax, __carry
+		      mov edx, 0
+		      adc edx, 0
+		      mov __sum, eax
+		      mov __carry, edx
+		    }
+
+		((unsigned int *)(__src + __ptrDelta))[0] = __sum;
+		__src += 4;
+		if (__carry == 0) {
+		    while (__src <= __srcLast4) {
+			/* copy over words */
+			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
+			__src += 4;
+		    }
+		    while (__src <= __srcLast) {
+			/* copy over bytes */
+			__src[__ptrDelta] = __src[0];
+			__src ++;
+		    }
+		    goto doneSource;
+		}
+	    }
+	}
 #  else /* not i386-WIN32 */
 #   if defined(__LSBFIRST__) && (__POINTER_SIZE__ == 8)
-        {
-            unsigned char *__srcLast4;
-
-            /*
-             * add long-wise
-             */
-            __srcLast4 = __srcLast - 3;
-            while (__src <= __srcLast4) {
-                unsigned INT __sum;
-
-                __sum = (INT)(((unsigned int *)__src)[0]);
-                __sum += __carry;
-                ((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
-                __src += 4;
-                __carry = __sum >> 32;
-                if (__carry == 0) {
-                    while (__src <= __srcLast4) {
-                        /* copy over words */
-                        ((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
-                        __src += 4;
-                    }
-                    while (__src <= __srcLast) {
-                        /* copy over bytes */
-                        __src[__ptrDelta] = __src[0];
-                        __src ++;
-                    }
-                    goto doneSource;
-                }
-            }
-        }
+	{
+	    unsigned char *__srcLast4;
+
+	    /*
+	     * add long-wise
+	     */
+	    __srcLast4 = __srcLast - 3;
+	    while (__src <= __srcLast4) {
+		unsigned INT __sum;
+
+		__sum = (INT)(((unsigned int *)__src)[0]);
+		__sum += __carry;
+		((unsigned int *)(__src + __ptrDelta))[0] = __sum /* & 0xFFFF */;
+		__src += 4;
+		__carry = __sum >> 32;
+		if (__carry == 0) {
+		    while (__src <= __srcLast4) {
+			/* copy over words */
+			((unsigned int *)(__src + __ptrDelta))[0] = ((unsigned int *)__src)[0];
+			__src += 4;
+		    }
+		    while (__src <= __srcLast) {
+			/* copy over bytes */
+			__src[__ptrDelta] = __src[0];
+			__src ++;
+		    }
+		    goto doneSource;
+		}
+	    }
+	}
 #   endif /* LSB+64bit */
 #  endif /* __i386__ & WIN32 */
 # endif /* __i386__ & GNUC */
 
-        /*
-         * add short-wise
-         */
-        while (__src < __srcLast) {
-            __carry += ((unsigned short *)__src)[0];
-            ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
-            __carry >>= 16;
-            __src += 2;
-        }
-        /*
-         * last (odd) byte
-         */
-        if (__src <= __srcLast) {
-            __carry += __src[0];
-            __src[__ptrDelta] = __carry /* & 0xFF */;
-            __carry >>= 8;
-            __src++;
-        }
+	/*
+	 * add short-wise
+	 */
+	while (__src < __srcLast) {
+	    __carry += ((unsigned short *)__src)[0];
+	    ((unsigned short *)(__src + __ptrDelta))[0] = __carry /* & 0xFFFF */;
+	    __carry >>= 16;
+	    __src += 2;
+	}
+	/*
+	 * last (odd) byte
+	 */
+	if (__src <= __srcLast) {
+	    __carry += __src[0];
+	    __src[__ptrDelta] = __carry /* & 0xFF */;
+	    __carry >>= 8;
+	    __src++;
+	}
 #else /* not __LSBFIRST__ */
 
-        /*
-         * add byte-wise
-         */
-        while (__src <= __srcLast) {
-            __carry += __src[0];
-            __src[__ptrDelta] = __carry /* & 0xFF */;
-            __src++;
-            __carry >>= 8;
-
-            if (__carry == 0) {
-                while (__src <= __srcLast) {
-                    /* copy over rest */
-                    __src[__ptrDelta] = __src[0];
-                    __src++;
-                }
-                goto doneSource;
-            }
-        }
+	/*
+	 * add byte-wise
+	 */
+	while (__src <= __srcLast) {
+	    __carry += __src[0];
+	    __src[__ptrDelta] = __carry /* & 0xFF */;
+	    __src++;
+	    __carry >>= 8;
+
+	    if (__carry == 0) {
+		while (__src <= __srcLast) {
+		    /* copy over rest */
+		    __src[__ptrDelta] = __src[0];
+		    __src++;
+		}
+		goto doneSource;
+	    }
+	}
 #endif /* __LSBFIRST__ */
 
     doneSource: ;
-        /*
-         * now, at most one other byte is to be stored ...
-         */
-        if (__len < __rsltLen) {
-            __src[__ptrDelta] = __carry /* & 0xFF */;
-            __src++;
-        }
-
-        if (__src[__ptrDelta-1] != 0) {      /* lastDigit */
-            RETURN (result);
-        }
-        // must compress
-        ok = true;
+	/*
+	 * now, at most one other byte is to be stored ...
+	 */
+	if (__len < __rsltLen) {
+	    __src[__ptrDelta] = __carry /* & 0xFF */;
+	    __src++;
+	}
+
+	if (__src[__ptrDelta-1] != 0) {      /* lastDigit */
+	    RETURN (result);
+	}
+	// must compress
+	ok = true;
     }
 %}.
 
     ok ~~ true ifTrue:[
-        index := 1.
-        carry := aSmallInteger abs.
-
-        [carry ~~ 0] whileTrue:[
-            (index <= len) ifTrue:[
-                carry := (digitByteArray basicAt:index) + carry.
-            ].
-            resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
-            carry := carry bitShift:-8.
-            index := index + 1
-        ].
-
-        (index <= rsltLen) ifTrue:[
-            [index <= len] whileTrue:[
-                resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
-                index := index + 1
-            ].
-            lastDigit := 0.
-        ].
-
-        (lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
-            ^ result
-        ].
+	index := 1.
+	carry := aSmallInteger abs.
+
+	[carry ~~ 0] whileTrue:[
+	    (index <= len) ifTrue:[
+		carry := (digitByteArray basicAt:index) + carry.
+	    ].
+	    resultDigitByteArray basicAt:index put:(lastDigit := carry bitAnd:16rFF).
+	    carry := carry bitShift:-8.
+	    index := index + 1
+	].
+
+	(index <= rsltLen) ifTrue:[
+	    [index <= len] whileTrue:[
+		resultDigitByteArray basicAt:index put:(digitByteArray basicAt:index).
+		index := index + 1
+	    ].
+	    lastDigit := 0.
+	].
+
+	(lastDigit ~~ 0 and:[rsltLen > SmallInteger maxBytes]) ifTrue:[
+	    ^ result
+	].
     ].
 
     ^ result compressed
@@ -4422,7 +4478,7 @@
     len2 := otherDigitByteArray size.
     lenRslt := len1 + len2.
     UseKarazuba ~~ false ifTrue:[
-        lenRslt > 400 ifTrue:[ ^ self absMulKarazuba:aLargeInteger ].
+	lenRslt > 400 ifTrue:[ ^ self absMulKarazuba:aLargeInteger ].
     ].
 
     result := self class basicNew numberOfDigits:lenRslt.
@@ -4432,198 +4488,198 @@
     if (__isByteArray(__INST(digitByteArray))
      && __isByteArray(otherDigitByteArray)
      && __isByteArray(resultDigitByteArray)) {
-        unsigned char *myBytes = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
-        unsigned char *otherBytes = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
-        unsigned char *resultBytes = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
-        unsigned char *_p1, *_pResult0, *_p1Last, *_p2Last;
-        unsigned INT _v;
-        int _len1 = __intVal(len1);
-        int _len2 = __intVal(len2);
-
-        _p1Last = myBytes    + _len1 - 1;  /* the last byte */
-        _p2Last = otherBytes + _len2 - 1;  /* the last byte */
-        _pResult0 = resultBytes;
-
-        /*
-         *         aaa...aaa      f1[0] * f2
-         * +      bbb...bbb       f1[1] * f2
-         * +     ccc...ccc        f1[2] * f2
-         * +    ...
-         * +   xxx...xxx          f1[high] * f2
-         *
-         * start short-wise
-         * bounds: (16rFFFF * 16rFFFF) + 16rFFFF -> FFFF0000
-         */
-        _p1 = myBytes;
+	unsigned char *myBytes = __ByteArrayInstPtr(__INST(digitByteArray))->ba_element;
+	unsigned char *otherBytes = __ByteArrayInstPtr(otherDigitByteArray)->ba_element;
+	unsigned char *resultBytes = __ByteArrayInstPtr(resultDigitByteArray)->ba_element;
+	unsigned char *_p1, *_pResult0, *_p1Last, *_p2Last;
+	unsigned INT _v;
+	int _len1 = __intVal(len1);
+	int _len2 = __intVal(len2);
+
+	_p1Last = myBytes    + _len1 - 1;  /* the last byte */
+	_p2Last = otherBytes + _len2 - 1;  /* the last byte */
+	_pResult0 = resultBytes;
+
+	/*
+	 *         aaa...aaa      f1[0] * f2
+	 * +      bbb...bbb       f1[1] * f2
+	 * +     ccc...ccc        f1[2] * f2
+	 * +    ...
+	 * +   xxx...xxx          f1[high] * f2
+	 *
+	 * start short-wise
+	 * bounds: (16rFFFF * 16rFFFF) + 16rFFFF -> FFFF0000
+	 */
+	_p1 = myBytes;
 
 #if defined(__LSBFIRST__) && (__POINTER_SIZE__ == 8)
-        /* loop over ints of f1 */
-        for (; _p1 <= (_p1Last-3); _p1 += 4, _pResult0 += 4) {
-            unsigned char *_pResult = _pResult0;
-            unsigned char *_p2;
-            unsigned INT word1 = ((unsigned int *)_p1)[0];
-
-            _v = 0;
-
-            /* loop over ints of f2 */
-            for (_p2 = otherBytes; _p2 <= (_p2Last-3); _p2 += 4) {
-                _v = word1 * (unsigned INT)(((unsigned int *)_p2)[0])
-                     + _v + (unsigned INT)((unsigned int *)_pResult)[0];
-                ((unsigned int *)_pResult)[0] = _v /* & 0xFFFFFFFF */;
-                _v >>= 32; /* now _v contains the carry*/
-                _pResult += 4;
-            }
-
-            /* possible odd up to 3 highBytes of f2 */
-            for ( ; _p2 <= _p2Last; _p2++) {
-                _v = word1 * (unsigned INT)(_p2[0])
-                     + _v + (unsigned INT)(_pResult[0]);
-
-                ((unsigned char *)_pResult)[0] = _v /* & 0xFFFFFFFF */;
-                _v >>= 8; /* now _v contains the carry*/
-                _pResult++;
-            }
-            /* distribute leftover carry byte-wise */
-            for ( ; _v; _v >>= 8, _pResult++) {
-                _v += _pResult[0];
-                _pResult[0] = _v /* & 0xFF */;
-            }
-        }
+	/* loop over ints of f1 */
+	for (; _p1 <= (_p1Last-3); _p1 += 4, _pResult0 += 4) {
+	    unsigned char *_pResult = _pResult0;
+	    unsigned char *_p2;
+	    unsigned INT word1 = ((unsigned int *)_p1)[0];
+
+	    _v = 0;
+
+	    /* loop over ints of f2 */
+	    for (_p2 = otherBytes; _p2 <= (_p2Last-3); _p2 += 4) {
+		_v = word1 * (unsigned INT)(((unsigned int *)_p2)[0])
+		     + _v + (unsigned INT)((unsigned int *)_pResult)[0];
+		((unsigned int *)_pResult)[0] = _v /* & 0xFFFFFFFF */;
+		_v >>= 32; /* now _v contains the carry*/
+		_pResult += 4;
+	    }
+
+	    /* possible odd up to 3 highBytes of f2 */
+	    for ( ; _p2 <= _p2Last; _p2++) {
+		_v = word1 * (unsigned INT)(_p2[0])
+		     + _v + (unsigned INT)(_pResult[0]);
+
+		((unsigned char *)_pResult)[0] = _v /* & 0xFFFFFFFF */;
+		_v >>= 8; /* now _v contains the carry*/
+		_pResult++;
+	    }
+	    /* distribute leftover carry byte-wise */
+	    for ( ; _v; _v >>= 8, _pResult++) {
+		_v += _pResult[0];
+		_pResult[0] = _v /* & 0xFF */;
+	    }
+	}
 #endif /* 64bit */
 
-        /* possible odd high short of f1 (or shortLoop, if not 64bit) */
-
-        for (; _p1 < _p1Last; _p1 += 2, _pResult0 += 2) {
-            unsigned char *_pResult = _pResult0;
-            unsigned char *_p2 = otherBytes;
-            unsigned int short1 = ((unsigned short *)_p1)[0];
+	/* possible odd high short of f1 (or shortLoop, if not 64bit) */
+
+	for (; _p1 < _p1Last; _p1 += 2, _pResult0 += 2) {
+	    unsigned char *_pResult = _pResult0;
+	    unsigned char *_p2 = otherBytes;
+	    unsigned int short1 = ((unsigned short *)_p1)[0];
 
 #if !defined(__LSBFIRST__)
-            short1 = ((short1 >> 8) & 0xFF) | ((short1 & 0xFF) << 8);
+	    short1 = ((short1 >> 8) & 0xFF) | ((short1 & 0xFF) << 8);
 #endif
-            _v = 0;
-
-            /* loop over shorts of f2 */
-            for ( ; _p2 < _p2Last; _p2 += 2, _pResult += 2) {
+	    _v = 0;
+
+	    /* loop over shorts of f2 */
+	    for ( ; _p2 < _p2Last; _p2 += 2, _pResult += 2) {
 #if !defined(__LSBFIRST__)
-                unsigned int _short2  = ((unsigned short *)_p2)[0];
-                unsigned int _short3  = ((unsigned short *)_pResult)[0];
-
-                _short2 = ((_short2 >> 8) /* & 0xFF */) | ((_short2 & 0xFF) << 8);
-                _short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
-                _v = (short1 * _short2) + _short3 + _v;
-                _pResult[0] = _v;
-                _pResult[1] = _v >> 8;
+		unsigned int _short2  = ((unsigned short *)_p2)[0];
+		unsigned int _short3  = ((unsigned short *)_pResult)[0];
+
+		_short2 = ((_short2 >> 8) /* & 0xFF */) | ((_short2 & 0xFF) << 8);
+		_short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
+		_v = (short1 * _short2) + _short3 + _v;
+		_pResult[0] = _v;
+		_pResult[1] = _v >> 8;
 #else /* __LSBFIRST__ */
-                _v = (short1 * ((unsigned short *)_p2)[0]) + _v + ((unsigned short *)_pResult)[0];
-                ((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
+		_v = (short1 * ((unsigned short *)_p2)[0]) + _v + ((unsigned short *)_pResult)[0];
+		((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
 #endif /* __LSBFIRST__ */
-                _v >>= 16; /* now _v contains the carry*/
-            }
-
-            /* possible odd highByte of f2 */
-            for ( ; _p2 <= _p2Last; _p2++, _pResult += 2) {
+		_v >>= 16; /* now _v contains the carry*/
+	    }
+
+	    /* possible odd highByte of f2 */
+	    for ( ; _p2 <= _p2Last; _p2++, _pResult += 2) {
 #if !defined(__LSBFIRST__)
-                unsigned int _short3 = ((unsigned short *)_pResult)[0];
-
-                _short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
-                _v = (short1 * _p2[0]) + _v + _short3;
-                _pResult[0] = _v;
-                _pResult[1] = _v >> 8;
+		unsigned int _short3 = ((unsigned short *)_pResult)[0];
+
+		_short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
+		_v = (short1 * _p2[0]) + _v + _short3;
+		_pResult[0] = _v;
+		_pResult[1] = _v >> 8;
 #else /* __LSBFIRST__ */
-                _v = (short1 * _p2[0]) + _v + ((unsigned short *)_pResult)[0];
-                ((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
+		_v = (short1 * _p2[0]) + _v + ((unsigned short *)_pResult)[0];
+		((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
 #endif /* __LSBFIRST__ */
-                _v >>= 16; /* now _v contains the carry*/
-            }
-            /* distribute leftover carry byte-wise */
-            for ( ; _v; _v >>= 8, _pResult++) {
-                _v += _pResult[0];
-                _pResult[0] = _v /* & 0xFF */;
-            }
-        }
-
-        /* possible odd highByte of f1 (or byteLoop, if above is ever disabled) */
-        for (; _p1 <= _p1Last; _p1++, _pResult0++) {
-            unsigned char *_pResult = _pResult0;
-            unsigned char *_p2 = otherBytes;
-            unsigned int byte1 = _p1[0];
-
-            _v = 0;
-
-            /* loop over shorts of f2 */
-            for ( ; _p2 < _p2Last; _p2 += 2, _pResult += 2) {
+		_v >>= 16; /* now _v contains the carry*/
+	    }
+	    /* distribute leftover carry byte-wise */
+	    for ( ; _v; _v >>= 8, _pResult++) {
+		_v += _pResult[0];
+		_pResult[0] = _v /* & 0xFF */;
+	    }
+	}
+
+	/* possible odd highByte of f1 (or byteLoop, if above is ever disabled) */
+	for (; _p1 <= _p1Last; _p1++, _pResult0++) {
+	    unsigned char *_pResult = _pResult0;
+	    unsigned char *_p2 = otherBytes;
+	    unsigned int byte1 = _p1[0];
+
+	    _v = 0;
+
+	    /* loop over shorts of f2 */
+	    for ( ; _p2 < _p2Last; _p2 += 2, _pResult += 2) {
 #if !defined(__LSBFIRST__)
-                unsigned int _short2 = ((unsigned short *)_p2)[0];
-                unsigned int _short3  = ((unsigned short *)_pResult)[0];
-
-                _short2 = ((_short2 >> 8) /* & 0xFF */) | ((_short2 & 0xFF) << 8);
-                _short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
-                _v = (byte1 * _short2) + _v +_short3;
-                _pResult[0] = _v;
-                _pResult[1] = _v >> 8;
+		unsigned int _short2 = ((unsigned short *)_p2)[0];
+		unsigned int _short3  = ((unsigned short *)_pResult)[0];
+
+		_short2 = ((_short2 >> 8) /* & 0xFF */) | ((_short2 & 0xFF) << 8);
+		_short3 = ((_short3 >> 8) /* & 0xFF */) | ((_short3 & 0xFF) << 8);
+		_v = (byte1 * _short2) + _v +_short3;
+		_pResult[0] = _v;
+		_pResult[1] = _v >> 8;
 #else /* __LSBFIRST__ */
-                _v = (byte1 * ((unsigned short *)_p2)[0]) + _v + ((unsigned short *)_pResult)[0];
-                ((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
+		_v = (byte1 * ((unsigned short *)_p2)[0]) + _v + ((unsigned short *)_pResult)[0];
+		((unsigned short *)_pResult)[0] = _v /* & 0xFFFF */;
 #endif /* __LSBFIRST__ */
-                _v >>= 16; /* now _v contains the carry*/
-            }
-
-            /* possible odd highByte of f2 (or byteLoop, if not __LSBFIRST__) */
-            for ( ; _p2 <= _p2Last; _p2++, _pResult++) {
-                _v = (byte1 * _p2[0]) + _v + _pResult[0];
-                _pResult[0] = _v /* & 0xFF */;
-                _v >>= 8; /* now _v contains the carry*/
-            }
-            /* distribute leftover carry byte-wise */
-            for ( ; _v; _v >>= 8, _pResult++) {
-                _v += _pResult[0];
-                _pResult[0] = _v /* & 0xFF */;
-            }
-        }
-        ok = true;
+		_v >>= 16; /* now _v contains the carry*/
+	    }
+
+	    /* possible odd highByte of f2 (or byteLoop, if not __LSBFIRST__) */
+	    for ( ; _p2 <= _p2Last; _p2++, _pResult++) {
+		_v = (byte1 * _p2[0]) + _v + _pResult[0];
+		_pResult[0] = _v /* & 0xFF */;
+		_v >>= 8; /* now _v contains the carry*/
+	    }
+	    /* distribute leftover carry byte-wise */
+	    for ( ; _v; _v >>= 8, _pResult++) {
+		_v += _pResult[0];
+		_pResult[0] = _v /* & 0xFF */;
+	    }
+	}
+	ok = true;
     }
 %}.
     ok ifFalse:[
-        1 to:len1 do:[:index1 |
-            1 to:len2 do:[:index2 |
-                dstIndex := index1 + index2 - 1.
-                prod := (digitByteArray basicAt:index1) * (otherDigitByteArray basicAt:index2).
-                prod := prod + (resultDigitByteArray basicAt:dstIndex).
-                resultDigitByteArray basicAt:dstIndex put:(prod bitAnd:16rFF).
-                carry := prod bitShift:-8.
-                carry ~~ 0 ifTrue:[
-                    idx := dstIndex + 1.
-                    [carry ~~ 0] whileTrue:[
-                        v := (resultDigitByteArray basicAt:idx) + carry.
-                        resultDigitByteArray basicAt:idx put:(v bitAnd:255).
-                        carry := v bitShift:-8.
-                        idx := idx + 1
-                    ]
-                ]
-            ]
-        ].
+	1 to:len1 do:[:index1 |
+	    1 to:len2 do:[:index2 |
+		dstIndex := index1 + index2 - 1.
+		prod := (digitByteArray basicAt:index1) * (otherDigitByteArray basicAt:index2).
+		prod := prod + (resultDigitByteArray basicAt:dstIndex).
+		resultDigitByteArray basicAt:dstIndex put:(prod bitAnd:16rFF).
+		carry := prod bitShift:-8.
+		carry ~~ 0 ifTrue:[
+		    idx := dstIndex + 1.
+		    [carry ~~ 0] whileTrue:[
+			v := (resultDigitByteArray basicAt:idx) + carry.
+			resultDigitByteArray basicAt:idx put:(v bitAnd:255).
+			carry := v bitShift:-8.
+			idx := idx + 1
+		    ]
+		]
+	    ]
+	].
     ].
     ^ result compressed
 !
 
 absMulKarazuba:aLargeInteger
     "return a LargeInteger representing abs(self) * abs(theArgument) using the karazuba algorithm.
-        a = (2^n * p) + q
-        b = (2^n * r) + s
-        a * b   = ((2^n * p) + q) * ((2^n * r) + s)
-                = 2^(n+n)*p*r + 2^n*p*s + 2^n*q*r + q*s
-                = 2^(n+n)*p*r + (p*r + q*s - (q-p)*(s-r))*2^n + q*s
-
-        this is faster for sufficient large n1,n2
-        because regular multiplication is O(n1*n2) and karazuma multiplies much smaller numbers
-        (half number of bits) but does more multiplications (on smaller numbers) and req's more
-        additions and subtractions (on smaller numbers).
-        The break-even for when to use regular multiplication has been determined heuristically
-        and is somewhere around 1600 bits (digitLength of 200).
-        (see test in absMul:)
-
-        To disable karazuba, set UseKarazuba to false.
+	a = (2^n * p) + q
+	b = (2^n * r) + s
+	a * b   = ((2^n * p) + q) * ((2^n * r) + s)
+		= 2^(n+n)*p*r + 2^n*p*s + 2^n*q*r + q*s
+		= 2^(n+n)*p*r + (p*r + q*s - (q-p)*(s-r))*2^n + q*s
+
+	this is faster for sufficient large n1,n2
+	because regular multiplication is O(n1*n2) and karazuma multiplies much smaller numbers
+	(half number of bits) but does more multiplications (on smaller numbers) and req's more
+	additions and subtractions (on smaller numbers).
+	The break-even for when to use regular multiplication has been determined heuristically
+	and is somewhere around 1600 bits (digitLength of 200).
+	(see test in absMul:)
+
+	To disable karazuba, set UseKarazuba to false.
     "
 
     "/ compute half-sized pi and qi...
@@ -4657,12 +4713,12 @@
 
     "
      #(100 500 1000 2500 5000 10000 25000 50000 100000 250000 500000 1000000) do:[:exp |
-         |nr r1 r2|
-         nr := (3 raisedTo:exp) asInteger.
-         Transcript show:exp; show:' nbytes: '; showCR:nr digitLength;
-            show:'  normal: '; show:(Time microsecondsToRun:[ UseKarazuba := false. r1 := nr * nr ]); showCR:'us';
-            show:'  karazuba: '; show:(Time microsecondsToRun:[ UseKarazuba := true. r2 := nr absMulKarazuba: nr]); showCR:'us'.
-         self assert:(r1 = r2).
+	 |nr r1 r2|
+	 nr := (3 raisedTo:exp) asInteger.
+	 Transcript show:exp; show:' nbytes: '; showCR:nr digitLength;
+	    show:'  normal: '; show:(Time microsecondsToRun:[ UseKarazuba := false. r1 := nr * nr ]); showCR:'us';
+	    show:'  karazuba: '; show:(Time microsecondsToRun:[ UseKarazuba := true. r2 := nr absMulKarazuba: nr]); showCR:'us'.
+	 self assert:(r1 = r2).
      ]
     "
 !
--- a/LongFloat.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/LongFloat.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1999 by eXept Software AG
 	      All Rights Reserved
@@ -1645,7 +1647,7 @@
      If you use this, be aware, that specifying long doubles differs on
      systems; on Linux/gnuc machines you have to give something like %LF/%LG.
      Also, the resulting string may not be longer than 255 bytes -
-     since thats the (static) size of the buffer.
+     since that's the (static) size of the buffer.
      This method is NONSTANDARD and may be removed without notice.
      WARNNG: this goes directly to the C-printf function and may therefore me inherently unsafe.
      Please use the printf: method, which is safe as it is completely implemented in Smalltalk."
@@ -1656,23 +1658,23 @@
     int len;
 
     if (__isStringLike(formatString)) {
-	/*
-	 * actually only needed on sparc: since thisContext is
-	 * in a global register, which gets destroyed by printf,
-	 * manually save it here - very stupid ...
-	 */
-	__BEGIN_PROTECT_REGISTERS__
-
-	len = snprintf(buffer, sizeof(buffer), __stringVal(formatString), __longFloatVal(self));
-
-	__END_PROTECT_REGISTERS__
-
-	if (len < 0) goto fail;
-
-	s = __MKSTRING_L(buffer, len);
-	if (s != nil) {
-	    RETURN (s);
-	}
+        /*
+         * actually only needed on sparc: since thisContext is
+         * in a global register, which gets destroyed by printf,
+         * manually save it here - very stupid ...
+         */
+        __BEGIN_PROTECT_REGISTERS__
+
+        len = snprintf(buffer, sizeof(buffer), __stringVal(formatString), __longFloatVal(self));
+
+        __END_PROTECT_REGISTERS__
+
+        if (len < 0) goto fail;
+
+        s = __MKSTRING_L(buffer, len);
+        if (s != nil) {
+            RETURN (s);
+        }
     }
 fail: ;
 %}.
--- a/Make.proto	Tue Sep 20 11:37:33 2016 +0100
+++ b/Make.proto	Mon Oct 03 12:44:41 2016 +0100
@@ -321,9 +321,7 @@
 $(OUTDIR)CharacterEncoderImplementations__ISO8859_9.$(O) CharacterEncoderImplementations__ISO8859_9.$(C) CharacterEncoderImplementations__ISO8859_9.$(H): CharacterEncoderImplementations__ISO8859_9.st $(INCLUDE_TOP)/stx/libbasic/CharacterEncoder.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterEncoderImplementations__ISO8859_1.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterEncoderImplementations__SingleByteEncoder.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)CharacterEncoderImplementations__KOI8_U.$(O) CharacterEncoderImplementations__KOI8_U.$(C) CharacterEncoderImplementations__KOI8_U.$(H): CharacterEncoderImplementations__KOI8_U.st $(INCLUDE_TOP)/stx/libbasic/CharacterEncoder.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterEncoderImplementations__KOI8_R.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterEncoderImplementations__SingleByteEncoder.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)CheapBlock.$(O) CheapBlock.$(C) CheapBlock.$(H): CheapBlock.st $(INCLUDE_TOP)/stx/libbasic/Block.$(H) $(INCLUDE_TOP)/stx/libbasic/CompiledCode.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutableFunction.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ClassBuildError.$(O) ClassBuildError.$(C) ClassBuildError.$(H): ClassBuildError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)CmdLineOptionError.$(O) CmdLineOptionError.$(C) CmdLineOptionError.$(H): CmdLineOptionError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)ElementBoundsError.$(O) ElementBoundsError.$(C) ElementBoundsError.$(H): ElementBoundsError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Fraction.$(O) Fraction.$(C) Fraction.$(H): Fraction.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticValue.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Number.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)GetOpt.$(O) GetOpt.$(C) GetOpt.$(H): GetOpt.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
 $(OUTDIR)IdentityDictionary.$(O) IdentityDictionary.$(C) IdentityDictionary.$(H): IdentityDictionary.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
@@ -369,9 +367,6 @@
 $(OUTDIR)AbortOperationRequest.$(O) AbortOperationRequest.$(C) AbortOperationRequest.$(H): AbortOperationRequest.st $(INCLUDE_TOP)/stx/libbasic/AbortAllOperationRequest.$(H) $(INCLUDE_TOP)/stx/libbasic/ControlRequest.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)AbstractNumberVector.$(O) AbstractNumberVector.$(C) AbstractNumberVector.$(H): AbstractNumberVector.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)AllocationFailure.$(O) AllocationFailure.$(C) AllocationFailure.$(H): AllocationFailure.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)AmbiguousMessage.$(O) AmbiguousMessage.$(C) AmbiguousMessage.$(H): AmbiguousMessage.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)ArithmeticError.$(O) ArithmeticError.$(C) ArithmeticError.$(H): ArithmeticError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)AssertionFailedError.$(O) AssertionFailedError.$(C) AssertionFailedError.$(H): AssertionFailedError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)AutoloadMetaclass.$(O) AutoloadMetaclass.$(C) AutoloadMetaclass.$(H): AutoloadMetaclass.st $(INCLUDE_TOP)/stx/libbasic/Behavior.$(H) $(INCLUDE_TOP)/stx/libbasic/ClassDescription.$(H) $(INCLUDE_TOP)/stx/libbasic/Metaclass.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ByteArray.$(O) ByteArray.$(C) ByteArray.$(H): ByteArray.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)CharacterArray.$(O) CharacterArray.$(C) CharacterArray.$(H): CharacterArray.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
@@ -379,7 +374,6 @@
 $(OUTDIR)Class.$(O) Class.$(C) Class.$(H): Class.st $(INCLUDE_TOP)/stx/libbasic/Array.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Association.$(H) $(INCLUDE_TOP)/stx/libbasic/Behavior.$(H) $(INCLUDE_TOP)/stx/libbasic/ClassDescription.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/LookupKey.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)ClassBuildWarning.$(O) ClassBuildWarning.$(C) ClassBuildWarning.$(H): ClassBuildWarning.st $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Notification.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/UserNotification.$(H) $(INCLUDE_TOP)/stx/libbasic/Warning.$(H) $(STCHDR)
 $(OUTDIR)ClassLoadInProgressQuery.$(O) ClassLoadInProgressQuery.$(C) ClassLoadInProgressQuery.$(H): ClassLoadInProgressQuery.st $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/LoadInProgressQuery.$(H) $(INCLUDE_TOP)/stx/libbasic/Notification.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Query.$(H) $(STCHDR)
-$(OUTDIR)ContextError.$(O) ContextError.$(C) ContextError.$(H): ContextError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)ConversionError.$(O) ConversionError.$(C) ConversionError.$(H): ConversionError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DeepCopyError.$(O) DeepCopyError.$(C) DeepCopyError.$(H): DeepCopyError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)ExceptionHandlerSet.$(O) ExceptionHandlerSet.$(C) ExceptionHandlerSet.$(H): ExceptionHandlerSet.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
@@ -392,9 +386,6 @@
 $(OUTDIR)InvalidPatchError.$(O) InvalidPatchError.$(C) InvalidPatchError.$(H): InvalidPatchError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)LargeInteger.$(O) LargeInteger.$(C) LargeInteger.$(H): LargeInteger.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticValue.$(H) $(INCLUDE_TOP)/stx/libbasic/Integer.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Number.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)LongFloat.$(O) LongFloat.$(C) LongFloat.$(H): LongFloat.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticValue.$(H) $(INCLUDE_TOP)/stx/libbasic/LimitedPrecisionReal.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Number.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)MessageNotUnderstood.$(O) MessageNotUnderstood.$(C) MessageNotUnderstood.$(H): MessageNotUnderstood.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)NoModificationError.$(O) NoModificationError.$(C) NoModificationError.$(H): NoModificationError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)NotFoundError.$(O) NotFoundError.$(C) NotFoundError.$(H): NotFoundError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)OSSignalInterrupt.$(O) OSSignalInterrupt.$(C) OSSignalInterrupt.$(H): OSSignalInterrupt.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)OsIllegalOperation.$(O) OsIllegalOperation.$(C) OsIllegalOperation.$(H): OsIllegalOperation.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OsError.$(H) $(STCHDR)
 $(OUTDIR)OsInaccessibleError.$(O) OsInaccessibleError.$(C) OsInaccessibleError.$(H): OsInaccessibleError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OsError.$(H) $(STCHDR)
@@ -409,92 +400,101 @@
 $(OUTDIR)ProceedError.$(O) ProceedError.$(C) ProceedError.$(H): ProceedError.st $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Notification.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/UserNotification.$(H) $(INCLUDE_TOP)/stx/libbasic/Warning.$(H) $(STCHDR)
 $(OUTDIR)ReadWriteStream.$(O) ReadWriteStream.$(C) ReadWriteStream.$(H): ReadWriteStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
 $(OUTDIR)ShortFloat.$(O) ShortFloat.$(C) ShortFloat.$(H): ShortFloat.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticValue.$(H) $(INCLUDE_TOP)/stx/libbasic/LimitedPrecisionReal.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Number.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
-$(OUTDIR)SignalError.$(O) SignalError.$(C) SignalError.$(H): SignalError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)SmallInteger.$(O) SmallInteger.$(C) SmallInteger.$(H): SmallInteger.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticValue.$(H) $(INCLUDE_TOP)/stx/libbasic/Integer.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/Number.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SmalltalkChunkFileSourceWriter.$(O) SmalltalkChunkFileSourceWriter.$(C) SmalltalkChunkFileSourceWriter.$(H): SmalltalkChunkFileSourceWriter.st $(INCLUDE_TOP)/stx/libbasic/AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)SomeNumber.$(O) SomeNumber.$(C) SomeNumber.$(H): SomeNumber.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticValue.$(H) $(INCLUDE_TOP)/stx/libbasic/Magnitude.$(H) $(INCLUDE_TOP)/stx/libbasic/MetaNumber.$(H) $(INCLUDE_TOP)/stx/libbasic/Number.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)StreamError.$(O) StreamError.$(C) StreamError.$(H): StreamError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)SubclassResponsibilityError.$(O) SubclassResponsibilityError.$(C) SubclassResponsibilityError.$(H): SubclassResponsibilityError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)TimeoutError.$(O) TimeoutError.$(C) TimeoutError.$(H): TimeoutError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)UnimplementedFunctionalityError.$(O) UnimplementedFunctionalityError.$(C) UnimplementedFunctionalityError.$(H): UnimplementedFunctionalityError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)UserPreferences.$(O) UserPreferences.$(C) UserPreferences.$(H): UserPreferences.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
 $(OUTDIR)VarArgCheapBlock.$(O) VarArgCheapBlock.$(C) VarArgCheapBlock.$(H): VarArgCheapBlock.st $(INCLUDE_TOP)/stx/libbasic/Block.$(H) $(INCLUDE_TOP)/stx/libbasic/CheapBlock.$(H) $(INCLUDE_TOP)/stx/libbasic/CompiledCode.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutableFunction.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)WeakIdentityDictionary.$(O) WeakIdentityDictionary.$(C) WeakIdentityDictionary.$(H): WeakIdentityDictionary.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
 $(OUTDIR)WeakValueIdentityDictionary.$(O) WeakValueIdentityDictionary.$(C) WeakValueIdentityDictionary.$(H): WeakValueIdentityDictionary.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(STCHDR)
+$(OUTDIR)AmbiguousMessage.$(O) AmbiguousMessage.$(C) AmbiguousMessage.$(H): AmbiguousMessage.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)ArgumentError.$(O) ArgumentError.$(C) ArgumentError.$(H): ArgumentError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)CannotResumeError.$(O) CannotResumeError.$(C) CannotResumeError.$(H): CannotResumeError.st $(INCLUDE_TOP)/stx/libbasic/ContextError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)CannotReturnError.$(O) CannotReturnError.$(C) CannotReturnError.$(H): CannotReturnError.st $(INCLUDE_TOP)/stx/libbasic/ContextError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)ArithmeticError.$(O) ArithmeticError.$(C) ArithmeticError.$(H): ArithmeticError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)AssertionFailedError.$(O) AssertionFailedError.$(C) AssertionFailedError.$(H): AssertionFailedError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)CharacterEncoderError.$(O) CharacterEncoderError.$(C) CharacterEncoderError.$(H): CharacterEncoderError.st $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)ClassBuildError.$(O) ClassBuildError.$(C) ClassBuildError.$(H): ClassBuildError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)ContextError.$(O) ContextError.$(C) ContextError.$(H): ContextError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DateConversionError.$(O) DateConversionError.$(C) DateConversionError.$(H): DateConversionError.st $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)DomainError.$(O) DomainError.$(C) DomainError.$(H): DomainError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DoubleArray.$(O) DoubleArray.$(C) DoubleArray.$(H): DoubleArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)ElementBoundsError.$(O) ElementBoundsError.$(C) ElementBoundsError.$(H): ElementBoundsError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)EndOfStreamError.$(O) EndOfStreamError.$(C) EndOfStreamError.$(H): EndOfStreamError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)ExternalStream.$(O) ExternalStream.$(C) ExternalStream.$(H): ExternalStream.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadWriteStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
 $(OUTDIR)ExternalStructure.$(O) ExternalStructure.$(C) ExternalStructure.$(H): ExternalStructure.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalBytes.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)FloatArray.$(O) FloatArray.$(C) FloatArray.$(H): FloatArray.st $(INCLUDE_TOP)/stx/libbasic/AbstractNumberVector.$(H) $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)ImmutableByteArray.$(O) ImmutableByteArray.$(C) ImmutableByteArray.$(H): ImmutableByteArray.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/ByteArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)IncompleteNextCountError.$(O) IncompleteNextCountError.$(C) IncompleteNextCountError.$(H): IncompleteNextCountError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
-$(OUTDIR)IndexNotFoundError.$(O) IndexNotFoundError.$(C) IndexNotFoundError.$(H): IndexNotFoundError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidCodeError.$(O) InvalidCodeError.$(C) InvalidCodeError.$(H): InvalidCodeError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidModeError.$(O) InvalidModeError.$(C) InvalidModeError.$(H): InvalidModeError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)InvalidOperationError.$(O) InvalidOperationError.$(C) InvalidOperationError.$(H): InvalidOperationError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)InvalidTypeError.$(O) InvalidTypeError.$(C) InvalidTypeError.$(H): InvalidTypeError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)KeyNotFoundError.$(O) KeyNotFoundError.$(C) KeyNotFoundError.$(H): KeyNotFoundError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)MallocFailure.$(O) MallocFailure.$(C) MallocFailure.$(H): MallocFailure.st $(INCLUDE_TOP)/stx/libbasic/AllocationFailure.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)MessageNotUnderstood.$(O) MessageNotUnderstood.$(C) MessageNotUnderstood.$(H): MessageNotUnderstood.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)MethodNotAppropriateError.$(O) MethodNotAppropriateError.$(C) MethodNotAppropriateError.$(H): MethodNotAppropriateError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)MissingClassInLiteralArrayErrorSignal.$(O) MissingClassInLiteralArrayErrorSignal.$(C) MissingClassInLiteralArrayErrorSignal.$(H): MissingClassInLiteralArrayErrorSignal.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)NoModificationError.$(O) NoModificationError.$(C) NoModificationError.$(H): NoModificationError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)NonBooleanReceiverError.$(O) NonBooleanReceiverError.$(C) NonBooleanReceiverError.$(H): NonBooleanReceiverError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)NotFoundError.$(O) NotFoundError.$(C) NotFoundError.$(H): NotFoundError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)NumberConversionError.$(O) NumberConversionError.$(C) NumberConversionError.$(H): NumberConversionError.st $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)OpenError.$(O) OpenError.$(C) OpenError.$(H): OpenError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)PackageNotFoundError.$(O) PackageNotFoundError.$(C) PackageNotFoundError.$(H): PackageNotFoundError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PackageLoadError.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)PositionError.$(O) PositionError.$(C) PositionError.$(H): PositionError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)PositionOutOfBoundsError.$(O) PositionOutOfBoundsError.$(C) PositionOutOfBoundsError.$(H): PositionOutOfBoundsError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)PrimitiveFailure.$(O) PrimitiveFailure.$(C) PrimitiveFailure.$(H): PrimitiveFailure.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)RangeError.$(O) RangeError.$(C) RangeError.$(H): RangeError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)ReadError.$(O) ReadError.$(C) ReadError.$(H): ReadError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)Registry.$(O) Registry.$(C) Registry.$(H): Registry.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(INCLUDE_TOP)/stx/libbasic/WeakIdentityDictionary.$(H) $(STCHDR)
+$(OUTDIR)SignalError.$(O) SignalError.$(C) SignalError.$(H): SignalError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)SignedByteArray.$(O) SignedByteArray.$(C) SignedByteArray.$(H): SignedByteArray.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/ByteArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)StreamIOError.$(O) StreamIOError.$(C) StreamIOError.$(H): StreamIOError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)StreamNotOpenError.$(O) StreamNotOpenError.$(C) StreamNotOpenError.$(H): StreamNotOpenError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)String.$(O) String.$(C) String.$(H): String.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)SubclassResponsibilityError.$(O) SubclassResponsibilityError.$(C) SubclassResponsibilityError.$(H): SubclassResponsibilityError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)TimeConversionError.$(O) TimeConversionError.$(C) TimeConversionError.$(H): TimeConversionError.st $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)TwoByteString.$(O) TwoByteString.$(C) TwoByteString.$(H): TwoByteString.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
-$(OUTDIR)UnorderedNumbersError.$(O) UnorderedNumbersError.$(C) UnorderedNumbersError.$(H): UnorderedNumbersError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)UnimplementedFunctionalityError.$(O) UnimplementedFunctionalityError.$(C) UnimplementedFunctionalityError.$(H): UnimplementedFunctionalityError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)UnprotectedExternalBytes.$(O) UnprotectedExternalBytes.$(C) UnprotectedExternalBytes.$(H): UnprotectedExternalBytes.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalBytes.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)WeakDependencyDictionary.$(O) WeakDependencyDictionary.$(C) WeakDependencyDictionary.$(H): WeakDependencyDictionary.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(INCLUDE_TOP)/stx/libbasic/WeakIdentityDictionary.$(H) $(STCHDR)
 $(OUTDIR)WriteError.$(O) WriteError.$(C) WriteError.$(H): WriteError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
-$(OUTDIR)WrongProceedabilityError.$(O) WrongProceedabilityError.$(C) WrongProceedabilityError.$(H): WrongProceedabilityError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/SignalError.$(H) $(STCHDR)
 $(OUTDIR)AbstractClassInstantiationError.$(O) AbstractClassInstantiationError.$(C) AbstractClassInstantiationError.$(H): AbstractClassInstantiationError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/MethodNotAppropriateError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)BadLiteralsError.$(O) BadLiteralsError.$(C) BadLiteralsError.$(H): BadLiteralsError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/InvalidCodeError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)CachingRegistry.$(O) CachingRegistry.$(C) CachingRegistry.$(H): CachingRegistry.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Registry.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(INCLUDE_TOP)/stx/libbasic/WeakIdentityDictionary.$(H) $(STCHDR)
+$(OUTDIR)CannotResumeError.$(O) CannotResumeError.$(C) CannotResumeError.$(H): CannotResumeError.st $(INCLUDE_TOP)/stx/libbasic/ContextError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)CannotReturnError.$(O) CannotReturnError.$(C) CannotReturnError.$(H): CannotReturnError.st $(INCLUDE_TOP)/stx/libbasic/ContextError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DecodingError.$(O) DecodingError.$(C) DecodingError.$(H): DecodingError.st $(INCLUDE_TOP)/stx/libbasic/CharacterEncoderError.$(H) $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)DomainError.$(O) DomainError.$(C) DomainError.$(H): DomainError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)EncodingError.$(O) EncodingError.$(C) EncodingError.$(H): EncodingError.st $(INCLUDE_TOP)/stx/libbasic/CharacterEncoderError.$(H) $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)FileDoesNotExistException.$(O) FileDoesNotExistException.$(C) FileDoesNotExistException.$(H): FileDoesNotExistException.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OpenError.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)FileStream.$(O) FileStream.$(C) FileStream.$(H): FileStream.st $(INCLUDE_TOP)/stx/libbasic/ExternalStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadWriteStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
 $(OUTDIR)HandleRegistry.$(O) HandleRegistry.$(C) HandleRegistry.$(H): HandleRegistry.st $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Dictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/IdentityDictionary.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/Registry.$(H) $(INCLUDE_TOP)/stx/libbasic/Set.$(H) $(INCLUDE_TOP)/stx/libbasic/WeakIdentityDictionary.$(H) $(STCHDR)
 $(OUTDIR)ImmutableString.$(O) ImmutableString.$(C) ImmutableString.$(H): ImmutableString.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/String.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)IndexNotFoundError.$(O) IndexNotFoundError.$(C) IndexNotFoundError.$(H): IndexNotFoundError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidByteCodeError.$(O) InvalidByteCodeError.$(C) InvalidByteCodeError.$(H): InvalidByteCodeError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/InvalidCodeError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidInstructionError.$(O) InvalidInstructionError.$(C) InvalidInstructionError.$(H): InvalidInstructionError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/InvalidCodeError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidReadError.$(O) InvalidReadError.$(C) InvalidReadError.$(H): InvalidReadError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)InvalidWriteError.$(O) InvalidWriteError.$(C) InvalidWriteError.$(H): InvalidWriteError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteError.$(H) $(STCHDR)
+$(OUTDIR)KeyNotFoundError.$(O) KeyNotFoundError.$(C) KeyNotFoundError.$(H): KeyNotFoundError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)MissingClassInLiteralArrayErrorSignal.$(O) MissingClassInLiteralArrayErrorSignal.$(C) MissingClassInLiteralArrayErrorSignal.$(H): MissingClassInLiteralArrayErrorSignal.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)NoByteCodeError.$(O) NoByteCodeError.$(C) NoByteCodeError.$(H): NoByteCodeError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/InvalidCodeError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)NonIntegerIndexError.$(O) NonIntegerIndexError.$(C) NonIntegerIndexError.$(H): NonIntegerIndexError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/IndexNotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)NonPositionableExternalStream.$(O) NonPositionableExternalStream.$(C) NonPositionableExternalStream.$(H): NonPositionableExternalStream.st $(INCLUDE_TOP)/stx/libbasic/ExternalStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadWriteStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
 $(OUTDIR)NumberFormatError.$(O) NumberFormatError.$(C) NumberFormatError.$(H): NumberFormatError.st $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NumberConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)OverflowError.$(O) OverflowError.$(C) OverflowError.$(H): OverflowError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/RangeError.$(H) $(STCHDR)
 $(OUTDIR)PTYOpenError.$(O) PTYOpenError.$(C) PTYOpenError.$(H): PTYOpenError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/OpenError.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/StreamError.$(H) $(STCHDR)
 $(OUTDIR)PackageNotCompatibleError.$(O) PackageNotCompatibleError.$(C) PackageNotCompatibleError.$(H): PackageNotCompatibleError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PackageLoadError.$(H) $(INCLUDE_TOP)/stx/libbasic/PackageNotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)SubscriptOutOfBoundsError.$(O) SubscriptOutOfBoundsError.$(C) SubscriptOutOfBoundsError.$(H): SubscriptOutOfBoundsError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/IndexNotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)RangeError.$(O) RangeError.$(C) RangeError.$(H): RangeError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)Symbol.$(O) Symbol.$(C) Symbol.$(H): Symbol.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/String.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
-$(OUTDIR)UnderflowError.$(O) UnderflowError.$(C) UnderflowError.$(H): UnderflowError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/RangeError.$(H) $(STCHDR)
 $(OUTDIR)Unicode16String.$(O) Unicode16String.$(C) Unicode16String.$(H): Unicode16String.st $(INCLUDE_TOP)/stx/libbasic/ArrayedCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/CharacterArray.$(H) $(INCLUDE_TOP)/stx/libbasic/Collection.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SequenceableCollection.$(H) $(INCLUDE_TOP)/stx/libbasic/TwoByteString.$(H) $(INCLUDE_TOP)/stx/libbasic/UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)UnorderedNumbersError.$(O) UnorderedNumbersError.$(C) UnorderedNumbersError.$(H): UnorderedNumbersError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)WrongNumberOfArgumentsError.$(O) WrongNumberOfArgumentsError.$(C) WrongNumberOfArgumentsError.$(H): WrongNumberOfArgumentsError.st $(INCLUDE_TOP)/stx/libbasic/ArgumentError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)ZeroDivide.$(O) ZeroDivide.$(C) ZeroDivide.$(H): ZeroDivide.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/DomainError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)WrongProceedabilityError.$(O) WrongProceedabilityError.$(C) WrongProceedabilityError.$(H): WrongProceedabilityError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/SignalError.$(H) $(STCHDR)
 $(OUTDIR)CharacterRangeError.$(O) CharacterRangeError.$(C) CharacterRangeError.$(H): CharacterRangeError.st $(INCLUDE_TOP)/stx/libbasic/CharacterEncoderError.$(H) $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/DecodingError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DirectoryStream.$(O) DirectoryStream.$(C) DirectoryStream.$(H): DirectoryStream.st $(INCLUDE_TOP)/stx/libbasic/ExternalStream.$(H) $(INCLUDE_TOP)/stx/libbasic/FileStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadWriteStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
 $(OUTDIR)InvalidEncodingError.$(O) InvalidEncodingError.$(C) InvalidEncodingError.$(H): InvalidEncodingError.st $(INCLUDE_TOP)/stx/libbasic/CharacterEncoderError.$(H) $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/DecodingError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)NonIntegerIndexError.$(O) NonIntegerIndexError.$(C) NonIntegerIndexError.$(H): NonIntegerIndexError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/IndexNotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)OverflowError.$(O) OverflowError.$(C) OverflowError.$(H): OverflowError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/RangeError.$(H) $(STCHDR)
 $(OUTDIR)PipeStream.$(O) PipeStream.$(C) PipeStream.$(H): PipeStream.st $(INCLUDE_TOP)/stx/libbasic/ExternalStream.$(H) $(INCLUDE_TOP)/stx/libbasic/NonPositionableExternalStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/PeekableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/PositionableStream.$(H) $(INCLUDE_TOP)/stx/libbasic/ReadWriteStream.$(H) $(INCLUDE_TOP)/stx/libbasic/Stream.$(H) $(INCLUDE_TOP)/stx/libbasic/WriteStream.$(H) $(STCHDR)
 $(OUTDIR)RomanNumberFormatError.$(O) RomanNumberFormatError.$(C) RomanNumberFormatError.$(H): RomanNumberFormatError.st $(INCLUDE_TOP)/stx/libbasic/ConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/NumberConversionError.$(H) $(INCLUDE_TOP)/stx/libbasic/NumberFormatError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)SubscriptOutOfBoundsError.$(O) SubscriptOutOfBoundsError.$(C) SubscriptOutOfBoundsError.$(H): SubscriptOutOfBoundsError.st $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/IndexNotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/NotFoundError.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)UnderflowError.$(O) UnderflowError.$(C) UnderflowError.$(H): UnderflowError.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(INCLUDE_TOP)/stx/libbasic/RangeError.$(H) $(STCHDR)
+$(OUTDIR)ZeroDivide.$(O) ZeroDivide.$(C) ZeroDivide.$(H): ZeroDivide.st $(INCLUDE_TOP)/stx/libbasic/ArithmeticError.$(H) $(INCLUDE_TOP)/stx/libbasic/DomainError.$(H) $(INCLUDE_TOP)/stx/libbasic/Error.$(H) $(INCLUDE_TOP)/stx/libbasic/Exception.$(H) $(INCLUDE_TOP)/stx/libbasic/ExecutionError.$(H) $(INCLUDE_TOP)/stx/libbasic/GenericException.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)UnixFileDescriptorHandle.$(O) UnixFileDescriptorHandle.$(C) UnixFileDescriptorHandle.$(H): UnixFileDescriptorHandle.st $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/OSFileHandle.$(H) $(INCLUDE_TOP)/stx/libbasic/OSHandle.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)UnixFileHandle.$(O) UnixFileHandle.$(C) UnixFileHandle.$(H): UnixFileHandle.st $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/OSFileHandle.$(H) $(INCLUDE_TOP)/stx/libbasic/OSHandle.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)UnixOperatingSystem.$(O) UnixOperatingSystem.$(C) UnixOperatingSystem.$(H): UnixOperatingSystem.st $(INCLUDE_TOP)/stx/libbasic/AbstractOperatingSystem.$(H) $(INCLUDE_TOP)/stx/libbasic/ExternalAddress.$(H) $(INCLUDE_TOP)/stx/libbasic/OSFileHandle.$(H) $(INCLUDE_TOP)/stx/libbasic/OSHandle.$(H) $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(INCLUDE_TOP)/stx/libbasic/SharedPool.$(H) $(STCHDR)
--- a/Make.spec	Tue Sep 20 11:37:33 2016 +0100
+++ b/Make.spec	Mon Oct 03 12:44:41 2016 +0100
@@ -22,7 +22,7 @@
 #                (if removed, they will be created as common
 #  -Pxxx       : defines the package
 #  -Zxxx       : a prefix for variables within the classLib
-#  -Dxxx       : defines passed to to CC for inline C-code
+#  -Dxxx       : defines passed to CC for inline C-code
 #  -Ixxx       : include path passed to CC for inline C-code
 #  +optspace   : optimized for space
 #  +optspace2  : optimized more for space
@@ -231,9 +231,7 @@
 	CharacterEncoderImplementations::ISO8859_9 \
 	CharacterEncoderImplementations::KOI8_U \
 	CheapBlock \
-	ClassBuildError \
 	CmdLineOptionError \
-	ElementBoundsError \
 	Fraction \
 	GetOpt \
 	IdentityDictionary \
@@ -279,9 +277,6 @@
 	AbortOperationRequest \
 	AbstractNumberVector \
 	AllocationFailure \
-	AmbiguousMessage \
-	ArithmeticError \
-	AssertionFailedError \
 	AutoloadMetaclass \
 	ByteArray \
 	CharacterArray \
@@ -289,7 +284,6 @@
 	Class \
 	ClassBuildWarning \
 	ClassLoadInProgressQuery \
-	ContextError \
 	ConversionError \
 	DeepCopyError \
 	ExceptionHandlerSet \
@@ -302,9 +296,6 @@
 	InvalidPatchError \
 	LargeInteger \
 	LongFloat \
-	MessageNotUnderstood \
-	NoModificationError \
-	NotFoundError \
 	OSSignalInterrupt \
 	OsIllegalOperation \
 	OsInaccessibleError \
@@ -319,92 +310,101 @@
 	ProceedError \
 	ReadWriteStream \
 	ShortFloat \
-	SignalError \
 	SmallInteger \
 	SmalltalkChunkFileSourceWriter \
 	SomeNumber \
 	StreamError \
-	SubclassResponsibilityError \
 	TimeoutError \
-	UnimplementedFunctionalityError \
 	UserPreferences \
 	VarArgCheapBlock \
 	WeakIdentityDictionary \
 	WeakValueIdentityDictionary \
+	AmbiguousMessage \
 	ArgumentError \
-	CannotResumeError \
-	CannotReturnError \
+	ArithmeticError \
+	AssertionFailedError \
 	CharacterEncoderError \
+	ClassBuildError \
+	ContextError \
 	DateConversionError \
-	DomainError \
 	DoubleArray \
+	ElementBoundsError \
 	EndOfStreamError \
 	ExternalStream \
 	ExternalStructure \
 	FloatArray \
 	ImmutableByteArray \
 	IncompleteNextCountError \
-	IndexNotFoundError \
 	InvalidCodeError \
 	InvalidModeError \
 	InvalidOperationError \
 	InvalidTypeError \
-	KeyNotFoundError \
 	MallocFailure \
+	MessageNotUnderstood \
 	MethodNotAppropriateError \
-	MissingClassInLiteralArrayErrorSignal \
+	NoModificationError \
 	NonBooleanReceiverError \
+	NotFoundError \
 	NumberConversionError \
 	OpenError \
 	PackageNotFoundError \
 	PositionError \
 	PositionOutOfBoundsError \
 	PrimitiveFailure \
-	RangeError \
 	ReadError \
 	Registry \
+	SignalError \
 	SignedByteArray \
 	StreamIOError \
 	StreamNotOpenError \
 	String \
+	SubclassResponsibilityError \
 	TimeConversionError \
 	TwoByteString \
-	UnorderedNumbersError \
+	UnimplementedFunctionalityError \
 	UnprotectedExternalBytes \
 	WeakDependencyDictionary \
 	WriteError \
-	WrongProceedabilityError \
 	AbstractClassInstantiationError \
 	BadLiteralsError \
 	CachingRegistry \
+	CannotResumeError \
+	CannotReturnError \
 	DecodingError \
+	DomainError \
 	EncodingError \
 	FileDoesNotExistException \
 	FileStream \
 	HandleRegistry \
 	ImmutableString \
+	IndexNotFoundError \
 	InvalidByteCodeError \
 	InvalidInstructionError \
 	InvalidReadError \
 	InvalidWriteError \
+	KeyNotFoundError \
+	MissingClassInLiteralArrayErrorSignal \
 	NoByteCodeError \
-	NonIntegerIndexError \
 	NonPositionableExternalStream \
 	NumberFormatError \
-	OverflowError \
 	PTYOpenError \
 	PackageNotCompatibleError \
-	SubscriptOutOfBoundsError \
+	RangeError \
 	Symbol \
-	UnderflowError \
 	Unicode16String \
+	UnorderedNumbersError \
 	WrongNumberOfArgumentsError \
-	ZeroDivide \
+	WrongProceedabilityError \
 	CharacterRangeError \
 	DirectoryStream \
 	InvalidEncodingError \
+	NonIntegerIndexError \
+	OverflowError \
 	PipeStream \
 	RomanNumberFormatError \
+	SubscriptOutOfBoundsError \
+	UnderflowError \
+	ZeroDivide \
 
 WIN32_CLASSES= \
 	Win32Process \
@@ -609,9 +609,7 @@
     $(OUTDIR_SLASH)CharacterEncoderImplementations__ISO8859_9.$(O) \
     $(OUTDIR_SLASH)CharacterEncoderImplementations__KOI8_U.$(O) \
     $(OUTDIR_SLASH)CheapBlock.$(O) \
-    $(OUTDIR_SLASH)ClassBuildError.$(O) \
     $(OUTDIR_SLASH)CmdLineOptionError.$(O) \
-    $(OUTDIR_SLASH)ElementBoundsError.$(O) \
     $(OUTDIR_SLASH)Fraction.$(O) \
     $(OUTDIR_SLASH)GetOpt.$(O) \
     $(OUTDIR_SLASH)IdentityDictionary.$(O) \
@@ -657,9 +655,6 @@
     $(OUTDIR_SLASH)AbortOperationRequest.$(O) \
     $(OUTDIR_SLASH)AbstractNumberVector.$(O) \
     $(OUTDIR_SLASH)AllocationFailure.$(O) \
-    $(OUTDIR_SLASH)AmbiguousMessage.$(O) \
-    $(OUTDIR_SLASH)ArithmeticError.$(O) \
-    $(OUTDIR_SLASH)AssertionFailedError.$(O) \
     $(OUTDIR_SLASH)AutoloadMetaclass.$(O) \
     $(OUTDIR_SLASH)ByteArray.$(O) \
     $(OUTDIR_SLASH)CharacterArray.$(O) \
@@ -667,7 +662,6 @@
     $(OUTDIR_SLASH)Class.$(O) \
     $(OUTDIR_SLASH)ClassBuildWarning.$(O) \
     $(OUTDIR_SLASH)ClassLoadInProgressQuery.$(O) \
-    $(OUTDIR_SLASH)ContextError.$(O) \
     $(OUTDIR_SLASH)ConversionError.$(O) \
     $(OUTDIR_SLASH)DeepCopyError.$(O) \
     $(OUTDIR_SLASH)ExceptionHandlerSet.$(O) \
@@ -680,9 +674,6 @@
     $(OUTDIR_SLASH)InvalidPatchError.$(O) \
     $(OUTDIR_SLASH)LargeInteger.$(O) \
     $(OUTDIR_SLASH)LongFloat.$(O) \
-    $(OUTDIR_SLASH)MessageNotUnderstood.$(O) \
-    $(OUTDIR_SLASH)NoModificationError.$(O) \
-    $(OUTDIR_SLASH)NotFoundError.$(O) \
     $(OUTDIR_SLASH)OSSignalInterrupt.$(O) \
     $(OUTDIR_SLASH)OsIllegalOperation.$(O) \
     $(OUTDIR_SLASH)OsInaccessibleError.$(O) \
@@ -697,92 +688,101 @@
     $(OUTDIR_SLASH)ProceedError.$(O) \
     $(OUTDIR_SLASH)ReadWriteStream.$(O) \
     $(OUTDIR_SLASH)ShortFloat.$(O) \
-    $(OUTDIR_SLASH)SignalError.$(O) \
     $(OUTDIR_SLASH)SmallInteger.$(O) \
     $(OUTDIR_SLASH)SmalltalkChunkFileSourceWriter.$(O) \
     $(OUTDIR_SLASH)SomeNumber.$(O) \
     $(OUTDIR_SLASH)StreamError.$(O) \
-    $(OUTDIR_SLASH)SubclassResponsibilityError.$(O) \
     $(OUTDIR_SLASH)TimeoutError.$(O) \
-    $(OUTDIR_SLASH)UnimplementedFunctionalityError.$(O) \
     $(OUTDIR_SLASH)UserPreferences.$(O) \
     $(OUTDIR_SLASH)VarArgCheapBlock.$(O) \
     $(OUTDIR_SLASH)WeakIdentityDictionary.$(O) \
     $(OUTDIR_SLASH)WeakValueIdentityDictionary.$(O) \
+    $(OUTDIR_SLASH)AmbiguousMessage.$(O) \
     $(OUTDIR_SLASH)ArgumentError.$(O) \
-    $(OUTDIR_SLASH)CannotResumeError.$(O) \
-    $(OUTDIR_SLASH)CannotReturnError.$(O) \
+    $(OUTDIR_SLASH)ArithmeticError.$(O) \
+    $(OUTDIR_SLASH)AssertionFailedError.$(O) \
     $(OUTDIR_SLASH)CharacterEncoderError.$(O) \
+    $(OUTDIR_SLASH)ClassBuildError.$(O) \
+    $(OUTDIR_SLASH)ContextError.$(O) \
     $(OUTDIR_SLASH)DateConversionError.$(O) \
-    $(OUTDIR_SLASH)DomainError.$(O) \
     $(OUTDIR_SLASH)DoubleArray.$(O) \
+    $(OUTDIR_SLASH)ElementBoundsError.$(O) \
     $(OUTDIR_SLASH)EndOfStreamError.$(O) \
     $(OUTDIR_SLASH)ExternalStream.$(O) \
     $(OUTDIR_SLASH)ExternalStructure.$(O) \
     $(OUTDIR_SLASH)FloatArray.$(O) \
     $(OUTDIR_SLASH)ImmutableByteArray.$(O) \
     $(OUTDIR_SLASH)IncompleteNextCountError.$(O) \
-    $(OUTDIR_SLASH)IndexNotFoundError.$(O) \
     $(OUTDIR_SLASH)InvalidCodeError.$(O) \
     $(OUTDIR_SLASH)InvalidModeError.$(O) \
     $(OUTDIR_SLASH)InvalidOperationError.$(O) \
     $(OUTDIR_SLASH)InvalidTypeError.$(O) \
-    $(OUTDIR_SLASH)KeyNotFoundError.$(O) \
     $(OUTDIR_SLASH)MallocFailure.$(O) \
+    $(OUTDIR_SLASH)MessageNotUnderstood.$(O) \
     $(OUTDIR_SLASH)MethodNotAppropriateError.$(O) \
-    $(OUTDIR_SLASH)MissingClassInLiteralArrayErrorSignal.$(O) \
+    $(OUTDIR_SLASH)NoModificationError.$(O) \
     $(OUTDIR_SLASH)NonBooleanReceiverError.$(O) \
+    $(OUTDIR_SLASH)NotFoundError.$(O) \
     $(OUTDIR_SLASH)NumberConversionError.$(O) \
     $(OUTDIR_SLASH)OpenError.$(O) \
     $(OUTDIR_SLASH)PackageNotFoundError.$(O) \
     $(OUTDIR_SLASH)PositionError.$(O) \
     $(OUTDIR_SLASH)PositionOutOfBoundsError.$(O) \
     $(OUTDIR_SLASH)PrimitiveFailure.$(O) \
-    $(OUTDIR_SLASH)RangeError.$(O) \
     $(OUTDIR_SLASH)ReadError.$(O) \
     $(OUTDIR_SLASH)Registry.$(O) \
+    $(OUTDIR_SLASH)SignalError.$(O) \
     $(OUTDIR_SLASH)SignedByteArray.$(O) \
     $(OUTDIR_SLASH)StreamIOError.$(O) \
     $(OUTDIR_SLASH)StreamNotOpenError.$(O) \
     $(OUTDIR_SLASH)String.$(O) \
+    $(OUTDIR_SLASH)SubclassResponsibilityError.$(O) \
     $(OUTDIR_SLASH)TimeConversionError.$(O) \
     $(OUTDIR_SLASH)TwoByteString.$(O) \
-    $(OUTDIR_SLASH)UnorderedNumbersError.$(O) \
+    $(OUTDIR_SLASH)UnimplementedFunctionalityError.$(O) \
     $(OUTDIR_SLASH)UnprotectedExternalBytes.$(O) \
     $(OUTDIR_SLASH)WeakDependencyDictionary.$(O) \
     $(OUTDIR_SLASH)WriteError.$(O) \
-    $(OUTDIR_SLASH)WrongProceedabilityError.$(O) \
     $(OUTDIR_SLASH)AbstractClassInstantiationError.$(O) \
     $(OUTDIR_SLASH)BadLiteralsError.$(O) \
     $(OUTDIR_SLASH)CachingRegistry.$(O) \
+    $(OUTDIR_SLASH)CannotResumeError.$(O) \
+    $(OUTDIR_SLASH)CannotReturnError.$(O) \
     $(OUTDIR_SLASH)DecodingError.$(O) \
+    $(OUTDIR_SLASH)DomainError.$(O) \
     $(OUTDIR_SLASH)EncodingError.$(O) \
     $(OUTDIR_SLASH)FileDoesNotExistException.$(O) \
     $(OUTDIR_SLASH)FileStream.$(O) \
     $(OUTDIR_SLASH)HandleRegistry.$(O) \
     $(OUTDIR_SLASH)ImmutableString.$(O) \
+    $(OUTDIR_SLASH)IndexNotFoundError.$(O) \
     $(OUTDIR_SLASH)InvalidByteCodeError.$(O) \
     $(OUTDIR_SLASH)InvalidInstructionError.$(O) \
     $(OUTDIR_SLASH)InvalidReadError.$(O) \
     $(OUTDIR_SLASH)InvalidWriteError.$(O) \
+    $(OUTDIR_SLASH)KeyNotFoundError.$(O) \
+    $(OUTDIR_SLASH)MissingClassInLiteralArrayErrorSignal.$(O) \
     $(OUTDIR_SLASH)NoByteCodeError.$(O) \
-    $(OUTDIR_SLASH)NonIntegerIndexError.$(O) \
     $(OUTDIR_SLASH)NonPositionableExternalStream.$(O) \
     $(OUTDIR_SLASH)NumberFormatError.$(O) \
-    $(OUTDIR_SLASH)OverflowError.$(O) \
     $(OUTDIR_SLASH)PTYOpenError.$(O) \
     $(OUTDIR_SLASH)PackageNotCompatibleError.$(O) \
-    $(OUTDIR_SLASH)SubscriptOutOfBoundsError.$(O) \
+    $(OUTDIR_SLASH)RangeError.$(O) \
     $(OUTDIR_SLASH)Symbol.$(O) \
-    $(OUTDIR_SLASH)UnderflowError.$(O) \
     $(OUTDIR_SLASH)Unicode16String.$(O) \
+    $(OUTDIR_SLASH)UnorderedNumbersError.$(O) \
     $(OUTDIR_SLASH)WrongNumberOfArgumentsError.$(O) \
-    $(OUTDIR_SLASH)ZeroDivide.$(O) \
+    $(OUTDIR_SLASH)WrongProceedabilityError.$(O) \
     $(OUTDIR_SLASH)CharacterRangeError.$(O) \
     $(OUTDIR_SLASH)DirectoryStream.$(O) \
     $(OUTDIR_SLASH)InvalidEncodingError.$(O) \
+    $(OUTDIR_SLASH)NonIntegerIndexError.$(O) \
+    $(OUTDIR_SLASH)OverflowError.$(O) \
     $(OUTDIR_SLASH)PipeStream.$(O) \
     $(OUTDIR_SLASH)RomanNumberFormatError.$(O) \
+    $(OUTDIR_SLASH)SubscriptOutOfBoundsError.$(O) \
+    $(OUTDIR_SLASH)UnderflowError.$(O) \
+    $(OUTDIR_SLASH)ZeroDivide.$(O) \
 
 WIN32_OBJS= \
     $(OUTDIR_SLASH)Win32Process.$(O) \
--- a/MessageNotUnderstood.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/MessageNotUnderstood.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2001 by eXept Software AG
               All Rights Reserved
@@ -15,7 +13,7 @@
 
 "{ NameSpace: Smalltalk }"
 
-ProceedableError subclass:#MessageNotUnderstood
+ExecutionError subclass:#MessageNotUnderstood
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -195,11 +193,11 @@
 !MessageNotUnderstood class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/MessageNotUnderstood.st,v 1.15 2015-04-28 21:18:21 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/MessageNotUnderstood.st,v 1.15 2015-04-28 21:18:21 cg Exp $'
+    ^ '$Header$'
 ! !
 
 
--- a/MiniDebugger.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/MiniDebugger.st	Mon Oct 03 12:44:41 2016 +0100
@@ -40,15 +40,22 @@
 documentation
 "
     a primitive (non graphical) debugger for use on systems without
-    graphics or when the real debugger dies (i.e. an error occurs in
-    the graphical debugger or the UI/event handler is broken).
-    Also, if an interrupt occurs within the debuger, this one is called for.
+    graphics or when the real debugger dies 
+    (i.e. an error occurs in the graphical debugger or the UI/event handler is broken).
+    This one is also called for, if an interrupt occurs within the debuger, 
+    or if CTRL-C is pressed in the controlling tty/console.
     Needs a console.
 
     MiniDebugger enter
 
+    Attention:
+        all printing is done via lowLevelErrorPrint,
+        to ensure that output is to stderr, even if a logger is present, or
+        Stderr has been set to some other stream (Transcript).
+        Also to avoid the logger's interfering and adding imestamp information.
+        
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 "
 ! !
 
@@ -62,6 +69,10 @@
         withMessage:'MiniDebugger'
         mayProceed:true
         input:nil
+
+    "
+     MiniDebugger enter
+    "
 !
 
 enter:aContext withMessage:aString mayProceed:mayProceed
@@ -85,25 +96,25 @@
         ex return
     ] do:[
         thisContext isRecursive ifTrue:[
-            "/ 'recursive error in debugger ignored' errorPrintCR.
+            "/ 'recursive lowLevelError in debugger ignored' lowLevelErrorPrintCR.
             ^ self
         ].
 
-        aString errorPrintCR.
+        aString lowLevelErrorPrintCR.
         Processor notNil ifTrue:[
             active := Processor activeProcess.
-            'process: id=' errorPrint. active id errorPrint.
-            ' name=' errorPrint. active name errorPrintCR.
+            'process: id=' lowLevelErrorPrint. active id lowLevelErrorPrint.
+            ' name=' lowLevelErrorPrint. active name lowLevelErrorPrintCR.
 
-            'context: ' errorPrint. aContext printString errorPrintCR.
+            'context: ' lowLevelErrorPrint. aContext printString lowLevelErrorPrintCR.
             (con := aContext) notNil ifTrue:[
                 con := con sender.
-                ' ......: ' errorPrint. con printString errorPrintCR.
+                ' ......: ' lowLevelErrorPrint. con printString lowLevelErrorPrintCR.
                 [con notNil] whileTrue:[
                     sender := con sender.
                     (sender notNil and:[sender selector == con selector]) ifTrue:[
-                        ' ......: ' errorPrint. sender printString errorPrintCR.
-                        ' ......:  [** intermediate recursive contexts skipped **]' errorPrintCR.
+                        ' ......: ' lowLevelErrorPrint. sender printString lowLevelErrorPrintCR.
+                        ' ......:  [** intermediate recursive contexts skipped **]' lowLevelErrorPrintCR.
                         [sender notNil
                          and:[sender selector == con selector
                          and:[sender method == con method]]] whileTrue:[
@@ -112,13 +123,13 @@
                         ].
                     ].
                     con := sender.
-                    ' ......: ' errorPrint. con printString errorPrintCR.
+                    ' ......: ' lowLevelErrorPrint. con printString lowLevelErrorPrintCR.
                 ]
             ]
         ].
         NotFirstTimeEntered ~~ true ifTrue:[
             NotFirstTimeEntered := true.
-            'Type "c" to proceed, "?" for help' errorPrintCR.
+            'Type "c" to proceed, "?" for help' lowLevelErrorPrintCR.
         ].
     ].
 
@@ -126,11 +137,11 @@
         Error handle:[:ex |
             ex return
         ] do:[
-            self warn:('Unexpected error:\' , aString , '\\No MiniDebugger functionality available') withCRs .
+            self warn:('Unexpected lowLevelError:\' , aString , '\\No MiniDebugger functionality available') withCRs .
         ].
 
         Error handle:[:ex |
-            'cannot raise Abort - exiting ...' errorPrintCR.
+            'cannot raise Abort - exiting ...' lowLevelErrorPrintCR.
             OperatingSystem exit:10.
         ] do:[
             AbortOperationRequest raise.
@@ -217,7 +228,7 @@
 !
 
 trace:aBlock
-    self trace:aBlock with:[:where | where errorPrintCR]
+    self trace:aBlock with:[:where | where lowLevelErrorPrintCR]
 
     "Modified: 20.5.1996 / 10:27:37 / cg"
 !
@@ -257,6 +268,10 @@
 
     |c leaveCmd stillHere yesNo|
 
+    Display notNil ifTrue:[
+        Display ungrabKeyboard; ungrabPointer.
+    ].
+    
     enteringContext := dot := aContext.
     nesting := 0.
     c := aContext.
@@ -270,17 +285,17 @@
     stillHere := true.
     [stillHere] whileTrue:[
         AbortOperationRequest handle:[:ex |
-            '** Abort caught - back in previous debugLevel' errorPrintCR.
+            '** Abort caught - back in previous debugLevel' lowLevelErrorPrintCR.
         ] do:[
             Error handle:[:ex |
                 StreamError handle:[:ex|
                     "You won't see this probably - but you will see it when doing a syscall trace"
-                    'Error while processing error in MiniDebugger (Stdout closed?):' errorPrintCR.
-                    ex description errorPrintCR.
+                    'Error while processing lowLevelError in MiniDebugger (Stdout closed?):' lowLevelErrorPrintCR.
+                    ex description lowLevelErrorPrintCR.
                     OperatingSystem exit:10.
                 ] do:[
-                    'Error while executing MiniDebugger command: ' errorPrint.
-                    ex description errorPrintCR.
+                    'Error while executing MiniDebugger command: ' lowLevelErrorPrint.
+                    ex description lowLevelErrorPrintCR.
                     yesNo := self getCommand:'- (i)gnore / (p)roceed / (d)ebug / b(acktrace) ? '.
                     yesNo == $d ifTrue:[
                         MiniDebugger enterWithMessage:'Debugging debugger' mayProceed:true.
@@ -310,7 +325,7 @@
             InterruptPending := 1
         ].
         (leaveCmd == $t) ifTrue: [
-            traceBlock := [:where | where fullPrint].
+            traceBlock := [:where | self printContext:where].
             ObjectMemory flushInlineCaches.
             ObjectMemory stepInterruptHandler:self.
             stillHere := false.
@@ -354,26 +369,26 @@
 
     where := thisContext.        "where is stepInterrupt context"
     where notNil ifTrue:[
-	where := where sender    "where is now interrupted methods context"
+        where := where sender    "where is now interrupted methods context"
     ].
     stepping ifTrue:[
-	where notNil ifTrue:[
-	    where fullPrint
-	] ifFalse:[
-	    'stepInterrupt: no context' errorPrintCR
-	].
-	self enter:where mayProceed:true
+        where notNil ifTrue:[
+            self printContext:where
+        ] ifFalse:[
+            'stepInterrupt: no context' lowLevelErrorPrintCR
+        ].
+        self enter:where mayProceed:true
     ] ifFalse:[
-	where notNil ifTrue:[
-	    traceBlock notNil ifTrue:[
-		traceBlock value:where
-	    ]
-	] ifFalse:[
-	    'traceInterrupt: no context' errorPrintCR
-	].
-	ObjectMemory flushInlineCaches.
-	StepInterruptPending := 1.
-	InterruptPending := 1
+        where notNil ifTrue:[
+            traceBlock notNil ifTrue:[
+                traceBlock value:where
+            ]
+        ] ifFalse:[
+            'traceInterrupt: no context' lowLevelErrorPrintCR
+        ].
+        ObjectMemory flushInlineCaches.
+        StepInterruptPending := 1.
+        InterruptPending := 1
     ]
 
     "Modified: / 20-05-1996 / 10:23:11 / cg"
@@ -449,22 +464,22 @@
 
     c := enteringContext.
     [ c notNil and:[ c sender ~~ dot ] ] whileTrue:[
-	c := c sender.
+        c := c sender.
     ].
     c notNil ifTrue:[
-	dot := c.
-	"/ dot fullPrint.
+        dot := c.
+        "/ dot fullPrint.
     ] ifFalse:[
-	'** dot is the bottom of the calling chain' errorPrintCR.
+        '** dot is the bottom of the calling chain' lowLevelErrorPrintCR.
     ].
 !
 
 moveDotUp
     dot sender notNil ifTrue:[
-	dot := dot sender.
-	"/ dot fullPrint.
+        dot := dot sender.
+        "/ dot fullPrint.
     ] ifFalse:[
-	'** dot is the top of the calling chain' errorPrintCR.
+        '** dot is the top of the calling chain' lowLevelErrorPrintCR.
     ].
 !
 
@@ -472,35 +487,52 @@
     |context n|
 
     aContext isNil ifTrue:[
-	'no context' errorPrintCR.
-	^ self
+        'no context' lowLevelErrorPrintCR.
+        ^ self
     ].
 
     context := aContext.
     n := commandCount.
     [context notNil] whileTrue: [
-	context fullPrint.
-	context := context sender.
-	n notNil ifTrue:[
-	    n := n - 1.
-	    n <= 0 ifTrue:[
-		^ self
-	    ]
-	]
+        self printContext:context.
+        context := context sender.
+        n notNil ifTrue:[
+            n := n - 1.
+            n <= 0 ifTrue:[
+                ^ self
+            ]
+        ]
     ]
 !
 
+printContext:aContext
+    "print the receiver, selector and args of the context"
+
+    "/ aContext fullPrint.
+
+    aContext receiverPrintString lowLevelErrorPrint. ' ' lowLevelErrorPrint. 
+    aContext selector asString lowLevelErrorPrint.
+    aContext argumentCount ~~ 0 ifTrue: [
+        ' ' lowLevelErrorPrint. aContext argsDisplayString lowLevelErrorPrint
+    ].
+    ' [' lowLevelErrorPrint. 
+    aContext lineNumber asString lowLevelErrorPrint. 
+    ']' lowLevelErrorPrintCR
+!
+
 printDot
-    dot fullPrint.
-    '  receiver: ' errorPrint. dot receiver errorPrintCR.
-    '  selector: ' errorPrint. dot selector errorPrintCR.
-    '  args: ' errorPrintCR.
+    self printContext:dot.
+    '  receiver: ' lowLevelErrorPrint. dot receiver printString lowLevelErrorPrintCR.
+    '  selector: ' lowLevelErrorPrint. dot selector lowLevelErrorPrintCR.
+    '  args: ' lowLevelErrorPrintCR.
     dot args keysAndValuesDo:[:idx :eachArg |
-	'    ' errorPrint. idx errorPrint. ': ' errorPrint. eachArg errorPrintCR.
+        '    ' lowLevelErrorPrint. idx  printString lowLevelErrorPrint. 
+        ': ' lowLevelErrorPrint. eachArg printString lowLevelErrorPrintCR.
     ].
-    '  vars: ' errorPrintCR.
+    '  vars: ' lowLevelErrorPrintCR.
     dot vars keysAndValuesDo:[:idx :eachVar |
-	'    ' errorPrint. idx errorPrint. ': ' errorPrint. eachVar errorPrintCR.
+        '    ' lowLevelErrorPrint. idx  printString lowLevelErrorPrint. 
+        ': ' lowLevelErrorPrint. eachVar printString lowLevelErrorPrintCR.
     ].
 !
 
@@ -514,32 +546,32 @@
     home := dot methodHome.
     mthd := home method.
     mthd isNil ifTrue:[
-	'** no source **' errorPrintCR.
-	^ self.
+        '** no source **' lowLevelErrorPrintCR.
+        ^ self.
     ].
     src := mthd source.
     src isNil ifTrue:[
-	'** no source **' errorPrintCR.
-	^ self.
+        '** no source **' lowLevelErrorPrintCR.
+        ^ self.
     ].
     pcLineNr := dot lineNumber.
 
     src := src asCollectionOfLines.
     full ifTrue:[
-	startLnr := 1.
-	stopLnr := src size.
+        startLnr := 1.
+        stopLnr := src size.
     ] ifFalse:[
-	startLnr := pcLineNr-10 max:1.
-	stopLnr := pcLineNr+10 min:src size.
+        startLnr := pcLineNr-10 max:1.
+        stopLnr := pcLineNr+10 min:src size.
     ].
     startLnr to:stopLnr do:[:lNr |
-	lNr == pcLineNr ifTrue:[
-	    '>> ' errorPrint.
-	] ifFalse:[
-	    '   ' errorPrint.
-	].
-	(lNr printStringLeftPaddedTo:3) errorPrint. ' ' errorPrint.
-	(src at:lNr) errorPrintCR.
+        lNr == pcLineNr ifTrue:[
+            '>> ' lowLevelErrorPrint.
+        ] ifFalse:[
+            '   ' lowLevelErrorPrint.
+        ].
+        (lNr printStringLeftPaddedTo:3) lowLevelErrorPrint. ' ' lowLevelErrorPrint.
+        (src at:lNr) asString lowLevelErrorPrintCR.
     ]
 !
 
@@ -580,8 +612,8 @@
     |con sig|
 
     (sig := AbortOperationRequest) isHandled ifTrue:[
-	sig raise.
-	'abort raise failed' errorPrintCR.
+        sig raise.
+        'abort raise failed' lowLevelErrorPrintCR.
     ].
 
     "TEMPORARY kludge - find event handler context
@@ -589,15 +621,15 @@
     "
     con := self findContext:#processEvent.
     con isNil ifTrue:[
-	con := self findContext:#dispatch.
+        con := self findContext:#dispatch.
     ].
     con notNil ifTrue:[
-	"got it"
-	con return.
-	'return failed' errorPrintCR.
+        "got it"
+        con return.
+        'return failed' lowLevelErrorPrintCR.
     ].
 
-    'found no context to resume' errorPrintCR.
+    'found no context to resume' lowLevelErrorPrintCR.
 
     "Modified: / 16.11.2001 / 17:39:14 / cg"
 !
@@ -628,13 +660,13 @@
 
     (cmd == $w) ifTrue:[
         proc notNil ifTrue:[
-            '-------- walkback of process ' errorPrint. id errorPrint. ' -------' errorPrintCR.
+            '-------- walkback of process ' lowLevelErrorPrint. id lowLevelErrorPrint. ' -------' lowLevelErrorPrintCR.
             self printBacktraceFrom:(proc suspendedContext)
         ] ifFalse:[
             id notNil ifTrue:[
-                'no process with id: ' errorPrint. id errorPrintCR.
+                'no process with id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
             ] ifFalse:[
-                '-------- walkback of current process -------' errorPrintCR.
+                '-------- walkback of current process -------' lowLevelErrorPrintCR.
                 self printBacktraceFrom:(self getContext)
             ]
         ].
@@ -643,7 +675,7 @@
 
     (cmd == $b) ifTrue:[
         proc notNil ifTrue:[
-            '-------- VM walkback of process ' errorPrint. id errorPrint. ' -------' errorPrintCR.
+            '-------- VM walkback of process ' lowLevelErrorPrint. id lowLevelErrorPrint. ' -------' lowLevelErrorPrintCR.
             (Processor activeProcess environmentAt:#Stderr ifAbsent:Stderr) == Stderr ifTrue:[
                 ObjectMemory printStackBacktraceFrom:(proc suspendedContext)
             ] ifFalse:[
@@ -652,9 +684,9 @@
             ].    
         ] ifFalse:[
             id notNil ifTrue:[
-                'no process with id: ' errorPrint. id errorPrintCR.
+                'no process with id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
             ] ifFalse:[
-                '-------- VM walkback of current process -------' errorPrintCR.
+                '-------- VM walkback of current process -------' lowLevelErrorPrintCR.
                 (Processor activeProcess environmentAt:#Stderr ifAbsent:Stderr) == Stderr ifTrue:[
                     ObjectMemory printStackBacktrace
                 ] ifFalse:[
@@ -667,9 +699,9 @@
     ].
 
     (cmd == $S) ifTrue:[
-        'saving "crash.img"...' errorPrint.
+        'saving "crash.img"...' lowLevelErrorPrint.
         ObjectMemory writeCrashImage.
-        'done.' errorPrintCR.
+        'done.' lowLevelErrorPrintCR.
         ^ false
     ].
     (cmd == $C) ifTrue:[
@@ -680,7 +712,7 @@
         OperatingSystem isMSWINDOWSlike ifTrue:[ changesFilename replaceAll:$: with:$_ ].
 
         ChangeSet current fileOutAs: changesFilename.
-        ('saved session changes to "',changesFilename,'".') errorPrintCR.
+        ('saved session changes to "',changesFilename,'".') lowLevelErrorPrintCR.
         ^ false
     ].
 
@@ -699,7 +731,7 @@
     ].
 
     (cmd == $r) ifTrue:[
-        dot receiver errorPrintCR.
+        dot receiver lowLevelErrorPrintCR.
         ^ false
     ].
 
@@ -724,7 +756,7 @@
         ^ false
     ].
     (cmd == $e) ifTrue:[
-        (Parser evaluate:commandArg) errorPrintCR.
+        (Parser evaluate:commandArg) lowLevelErrorPrintCR.
         ^ false
     ].
 
@@ -744,7 +776,7 @@
         (bool notNil) ifTrue:[
             Smalltalk ignoreHalt:bool not.
         ].
-        'halts are ' errorPrint. (Smalltalk ignoreHalt ifTrue:['disabled'] ifFalse:['enabled']) errorPrintCR.
+        'halts are ' lowLevelErrorPrint. (Smalltalk ignoreHalt ifTrue:['disabled'] ifFalse:['enabled']) lowLevelErrorPrintCR.
         ^ false
     ].
 
@@ -760,7 +792,7 @@
             proc terminate.
         ] ifFalse:[
             id notNil ifTrue:[
-                'no process with id: ' errorPrint. id errorPrintCR.
+                'no process with id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
             ] ifFalse:[
                 Processor terminateActive
             ]
@@ -770,10 +802,10 @@
 
     (cmd == $W) ifTrue:[
         proc notNil ifTrue:[
-            'stopping process id: ' errorPrint. id errorPrintCR.
+            'stopping process id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
             proc stop.
         ] ifFalse:[
-            'invalid process id: ' errorPrint. id errorPrintCR.
+            'invalid process id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
         ].
         ^ false
     ].
@@ -781,10 +813,10 @@
     (cmd == $a) ifTrue:[
         "without id-arg, this is handled by caller"
         proc notNil ifTrue:[
-            'aborting process id: ' errorPrint. id errorPrintCR.
+            'aborting process id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
             proc interruptWith:[AbortOperationRequest raise]
         ] ifFalse:[
-            'aborting' errorPrintCR.
+            'aborting' lowLevelErrorPrintCR.
         ].
         ^ false
     ].
@@ -794,7 +826,7 @@
             proc terminateNoSignal.
         ] ifFalse:[
             id notNil ifTrue:[
-                'no process with id: ' errorPrint. id errorPrintCR.
+                'no process with id: ' lowLevelErrorPrint. id lowLevelErrorPrintCR.
             ] ifFalse:[
                 Processor terminateActiveNoSignal
             ]
@@ -871,7 +903,7 @@
             'MiniDebugger> '
           ] ifFalse:[
             'MiniDebugger' , nesting printString , '>'
-          ])) errorPrint.
+          ])) lowLevelErrorPrint.
 
     UserInterrupt handle:[:ex |
         ex restart
@@ -880,10 +912,10 @@
 
         cmd := self getCharacter.
         cmd isNil ifTrue:[
-            '<EOF>' errorPrintCR.
+            '<EOF>' lowLevelErrorPrintCR.
             "
              mhmh end-of-file;
-             return a 'c' (for continue); hope thats ok.
+             return a 'c' (for continue); hope that's ok.
             "
             cmd := $c
         ].
@@ -898,7 +930,7 @@
             [cmd notNil and:[cmd == Character space]] whileTrue:[
                 cmd := self getCharacter
             ].
-            cmd isNil ifTrue:[ '<EOF>' errorPrintCR ].
+            cmd isNil ifTrue:[ '<EOF>' lowLevelErrorPrintCR ].
         ].
 
         "
@@ -909,7 +941,7 @@
         [c isNil or:[c isEndOfLineCharacter]] whileFalse: [
             arg := arg copyWith:c.
             c := self getCharacter.
-            c isNil ifTrue:[ '<EOF>' errorPrintCR ].
+            c isNil ifTrue:[ '<EOF>' lowLevelErrorPrintCR ].
         ].
         commandArg := (arg copyFrom:2) withoutSeparators.
         command := cmd.
@@ -924,50 +956,50 @@
     |args className sym val match showMethod|
 
     commandArg withoutSeparators isEmpty ifTrue:[
-	'usage: H className [methodPattern]' errorPrintCR.
-	^self
+        'usage: H className [methodPattern]' lowLevelErrorPrintCR.
+        ^self
     ].
     args := commandArg asCollectionOfWords.
     className := args first.
 
     (sym := className asSymbolIfInterned) isNil ifTrue:[
-	'no such class' errorPrintCR.
-	^ self.
+        'no such class' lowLevelErrorPrintCR.
+        ^ self.
     ].
-    val := Smalltalk at:sym ifAbsent:['no such class' errorPrintCR. ^ self.].
+    val := Smalltalk at:sym ifAbsent:['no such class' lowLevelErrorPrintCR. ^ self.].
     val isBehavior ifFalse:[
-	'not a class: ' errorPrint. className errorPrintCR.
-	val := val class.
-	'showing help for ' errorPrint. val name errorPrintCR.
+        'not a class: ' lowLevelErrorPrint. className lowLevelErrorPrintCR.
+        val := val class.
+        'showing help for ' lowLevelErrorPrint. val name lowLevelErrorPrintCR.
     ].
     args size > 1 ifTrue:[
-	match := args at:2
+        match := args at:2
     ] ifFalse:[
-	match := '*'
+        match := '*'
     ].
 
     showMethod :=
-	[:sel :cls |
-	    |mthd|
+        [:sel :cls |
+            |mthd|
 
-	    ((match includesMatchCharacters and:[ sel matches:match caseSensitive:false])
-	    or:[ sel asLowercase startsWith:match asLowercase ]) ifTrue:[
-		mthd := cls compiledMethodAt:sel.
-		mthd category ~= 'documentation' ifTrue:[
-		    sel errorPrintCR.
-		    (mthd comment ? '') asStringCollection do:[:l |
-			'    ' errorPrint. l withoutSeparators errorPrintCR.
-		    ].
-		    '' errorPrintCR
-		].
-	    ].
-	].
+            ((match includesMatchCharacters and:[ sel matches:match caseSensitive:false])
+            or:[ sel asLowercase startsWith:match asLowercase ]) ifTrue:[
+                mthd := cls compiledMethodAt:sel.
+                mthd category ~= 'documentation' ifTrue:[
+                    sel lowLevelErrorPrintCR.
+                    (mthd comment ? '') asStringCollection do:[:l |
+                        '    ' lowLevelErrorPrint. l withoutSeparators lowLevelErrorPrintCR.
+                    ].
+                    '' lowLevelErrorPrintCR
+                ].
+            ].
+        ].
 
     val theMetaclass selectors copy sort do:[:sel |
-	showMethod value:sel value:val theMetaclass
+        showMethod value:sel value:val theMetaclass
     ].
     val theNonMetaclass selectors copy sort do:[:sel |
-	showMethod value:sel value:val theNonMetaclass
+        showMethod value:sel value:val theNonMetaclass
     ].
 !
 
@@ -1011,18 +1043,18 @@
 
 printAllBacktraces
     Process allInstancesDo:[:p |
-	(p isActive not
-	and:[p isDead not]) ifTrue:[
-	    '---------------------------------------------------------' errorPrintCR.
-	    '  proc id=' errorPrint. p id errorPrint.
-	    ' name=''' errorPrint. p name errorPrint.
-	    ''' createdBy: ' errorPrint. p creatorId errorPrint.
-	    ' state=' errorPrint.  p state errorPrint.
-	    ' prio=' errorPrint. p priority errorPrintCR.
-	    '' errorPrintCR. '' errorPrintCR.
+        (p isActive not
+        and:[p isDead not]) ifTrue:[
+            '---------------------------------------------------------' lowLevelErrorPrintCR.
+            '  proc id=' lowLevelErrorPrint. p id asString lowLevelErrorPrint.
+            ' name=''' lowLevelErrorPrint. p name asString lowLevelErrorPrint.
+            ''' createdBy: ' lowLevelErrorPrint. p creatorId asString lowLevelErrorPrint.
+            ' state=' lowLevelErrorPrint.  p state asString lowLevelErrorPrint.
+            ' prio=' lowLevelErrorPrint. p priority asString lowLevelErrorPrintCR.
+            '' lowLevelErrorPrintCR. '' lowLevelErrorPrintCR.
 
-	    self printBacktraceFrom:(p suspendedContext)
-	]
+            self printBacktraceFrom:(p suspendedContext)
+        ]
     ]
 !
 
@@ -1034,25 +1066,27 @@
     |active|
 
     active := Processor activeProcess.
-    'current id=' errorPrint. active id errorPrint. ' name=''' errorPrint. active name errorPrint. '''' errorPrintCR.
+    'current id=' lowLevelErrorPrint. 
+    active id printString lowLevelErrorPrint. 
+    ' name=''' lowLevelErrorPrint. active name lowLevelErrorPrint. '''' lowLevelErrorPrintCR.
 
     (Process allSubInstances sort:[:a :b | (a id ? -1)<(b id ? -1)]) do:[:p |
-	|doShow|
+        |doShow|
 
-	doShow := (how == #all).
-	doShow := doShow or:[ (how == #dead) and:[ p isDead ]].
-	doShow := doShow or:[ (how ~~ #dead) and:[ p isDead not ]].
-	doShow ifTrue:[
-	    'proc id=' errorPrint. (p id printStringPaddedTo:6) errorPrint.
-	    (p state printStringPaddedTo:10) errorPrint.
-	    ' pri=' errorPrint. (p priority printStringPaddedTo:2) errorPrint.
-	    ' creator:' errorPrint. (p creatorId printStringPaddedTo:5) errorPrint.
-	    ' group:' errorPrint. (p processGroupId printStringPaddedTo:5) errorPrint.
-	    ' sys:' errorPrint. (p isSystemProcess ifTrue:'y' ifFalse:'n') errorPrint.
-	    ' ui:' errorPrint. (p isGUIProcess ifTrue:'y' ifFalse:'n') errorPrint.
-	    ' name=''' errorPrint. p name errorPrint.
-	    '''' errorPrintCR.
-	]
+        doShow := (how == #all).
+        doShow := doShow or:[ (how == #dead) and:[ p isDead ]].
+        doShow := doShow or:[ (how ~~ #dead) and:[ p isDead not ]].
+        doShow ifTrue:[
+            'proc id=' lowLevelErrorPrint. (p id printStringPaddedTo:6) lowLevelErrorPrint.
+            (p state printStringPaddedTo:10) lowLevelErrorPrint.
+            ' pri=' lowLevelErrorPrint. (p priority printStringPaddedTo:2) lowLevelErrorPrint.
+            ' creator:' lowLevelErrorPrint. (p creatorId printStringPaddedTo:5) lowLevelErrorPrint.
+            ' group:' lowLevelErrorPrint. (p processGroupId printStringPaddedTo:5) lowLevelErrorPrint.
+            ' sys:' lowLevelErrorPrint. (p isSystemProcess ifTrue:'y' ifFalse:'n') lowLevelErrorPrint.
+            ' ui:' lowLevelErrorPrint. (p isGUIProcess ifTrue:'y' ifFalse:'n') lowLevelErrorPrint.
+            ' name=''' lowLevelErrorPrint. p name lowLevelErrorPrint.
+            '''' lowLevelErrorPrintCR.
+        ]
     ]
 
     "Modified: / 31.7.1998 / 16:30:19 / cg"
@@ -1096,7 +1130,7 @@
    I ........ interpreter (expression evaluator)
    e expr ... evaluate expression & print result ("E" to not print)
    ? c [p] .. help on class c (selectors matching p)
-'  errorPrintCR.
+'  lowLevelErrorPrintCR.
 
    (XWorkstation notNil and:[ Screen default isKindOf:XWorkstation ]) ifTrue:[
 '   To repair a broken X-Connection, enter an interpreter (enter "I") and evaluate:
@@ -1106,7 +1140,7 @@
       NewLauncher openOnDevice:Display.
       #exit
     then enter "c" to continue; a NewLauncher should pop up soon.
-'  errorPrintCR
+'  lowLevelErrorPrintCR
     ]
 
     "Modified: / 03-02-2014 / 10:38:36 / cg"
--- a/MiniLogger.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/MiniLogger.st	Mon Oct 03 12:44:41 2016 +0100
@@ -15,8 +15,8 @@
 
 Object subclass:#MiniLogger
 	instanceVariableNames:''
-	classVariableNames:'ALL ENTER LEAVE TRACE3 TRACE2 TRACE1 TRACE0 TRACE DEBUG INFO WARN
-		ERROR FATAL NONE Severities Threshold Instance'
+	classVariableNames:'ALL DEBUG ENTER ERROR FATAL INFO Instance LEAVE NONE Severities
+		TRACE TRACE0 TRACE1 TRACE2 TRACE3 Threshold WARN WARNING'
 	poolDictionaries:''
 	category:'System-Debugging-Support'
 !
@@ -114,11 +114,12 @@
     DEBUG := Severity new initializeWithName:#debug value:60.
     INFO := Severity new initializeWithName:#info value:70.
     WARN := Severity new initializeWithName:#warn value:88.
+    WARNING := Severity new initializeWithName:#warning value:88.
     ERROR := Severity new initializeWithName:#error value:99.
     FATAL := Severity new initializeWithName:#fatal value:100.
     NONE := Severity new initializeWithName:#none value:65535.
 
-    Severities := Array new:12.
+    Severities := Array new:13.
     Severities at:1 put:ENTER.
     Severities at:2 put:LEAVE.
     Severities at:3 put:TRACE3.
@@ -129,8 +130,9 @@
     Severities at:8 put:DEBUG.
     Severities at:9 put:INFO.
     Severities at:10 put:WARN.
-    Severities at:11 put:ERROR.
-    Severities at:12 put:FATAL.
+    Severities at:11 put:WARNING.
+    Severities at:12 put:ERROR.
+    Severities at:13 put:FATAL.
 
     Threshold := InfoPrinting ifTrue:[INFO] ifFalse:[WARN].
 
@@ -256,6 +258,7 @@
     "
     Logger loggingThreshold: Logger severityALL.
     Logger loggingThreshold: Logger severityINFO.
+    Logger loggingThreshold: Logger severityNONE.
     "
 
     "Created: / 13-08-2014 / 14:34:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -402,6 +405,13 @@
     "Modified: / 02-12-2014 / 10:54:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+debug: format with: arg1 with: arg2 with:arg3
+    DEBUG value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: DEBUG originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:54:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 enter: message
     ENTER value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: ENTER originator: thisContext sender receiver
@@ -423,6 +433,13 @@
     "Modified: / 02-12-2014 / 10:54:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+enter: format with: arg1 with: arg2 with:arg3
+    ENTER value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: ENTER originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:54:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 error: message
     ERROR value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: ERROR originator: thisContext sender receiver
@@ -444,6 +461,13 @@
     "Modified: / 02-12-2014 / 10:54:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+error: format with: arg1 with: arg2 with:arg3
+    ERROR value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: ERROR originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:54:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 fatal: message
     FATAL value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: FATAL originator: thisContext sender receiver
@@ -465,6 +489,13 @@
     "Modified: / 02-12-2014 / 10:54:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+fatal: format with: arg1 with: arg2 with:arg3
+    FATAL value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: FATAL originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:54:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 info: message
     INFO value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: INFO originator: thisContext sender receiver
@@ -486,6 +517,13 @@
     "Modified: / 02-12-2014 / 10:55:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+info: format with: arg1 with: arg2 with:arg3
+    INFO value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: INFO originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:55:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 leave: message
     LEAVE value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: LEAVE originator: thisContext sender receiver
@@ -507,6 +545,13 @@
     "Modified: / 02-12-2014 / 10:55:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+leave: format with: arg1 with: arg2 with:arg3
+    LEAVE value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: LEAVE originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:55:22 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 trace0: message
     TRACE0 value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: TRACE0 originator: thisContext sender receiver
@@ -528,6 +573,13 @@
     "Modified: / 02-12-2014 / 10:55:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+trace0: format with: arg1 with: arg2 with:arg3
+    TRACE0 value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: TRACE0 originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:55:31 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 trace1: message
     TRACE1 value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: TRACE1 originator: thisContext sender receiver
@@ -549,6 +601,13 @@
     "Modified: / 02-12-2014 / 10:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+trace1: format with: arg1 with: arg2 with:arg3
+    TRACE1 value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: TRACE1 originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:55:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 trace2: message
     TRACE2 value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: TRACE2 originator: thisContext sender receiver
@@ -570,6 +629,13 @@
     "Modified: / 02-12-2014 / 10:55:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+trace2: format with: arg1 with: arg2 with:arg3
+    TRACE2 value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: TRACE2 originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:55:52 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 trace3: message
     TRACE3 value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: TRACE3 originator: thisContext sender receiver
@@ -591,6 +657,13 @@
     "Modified: / 02-12-2014 / 10:56:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+trace3: format with: arg1 with: arg2 with:arg3
+    TRACE3 value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: TRACE3 originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:56:03 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 trace: message
     TRACE value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: TRACE originator: thisContext sender receiver
@@ -612,6 +685,13 @@
     "Modified: / 02-12-2014 / 10:56:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+trace: format with: arg1 with: arg2 with:arg3
+    TRACE value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith: arg1 with: arg2 with:arg3) severity: TRACE originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:56:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 warning: message
     WARN value < Threshold value ifTrue:[ ^ self ].
     self log: message severity: WARN originator: thisContext sender receiver
@@ -626,11 +706,18 @@
     "Modified: / 02-12-2014 / 10:56:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-warning: format with: arg1 with: arg2
+warning:format with:arg1 with:arg2
     WARN value < Threshold value ifTrue:[ ^ self ].
     self log: (format bindWith: arg1 with: arg2) severity: WARN originator: thisContext sender receiver
 
     "Modified: / 02-12-2014 / 10:56:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+warning:format with:arg1 with:arg2 with:arg3
+    WARN value < Threshold value ifTrue:[ ^ self ].
+    self log: (format bindWith:arg1 with:arg2 with:arg3) severity: WARN originator: thisContext sender receiver
+
+    "Modified: / 02-12-2014 / 10:56:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !MiniLogger class methodsFor:'private'!
@@ -657,12 +744,15 @@
     "Created: / 15-09-2011 / 10:20:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-log: message severity: severity facility: facility originator: originator attachment: attachment on:aStream
+log: message severity: severity facility: facilityArg originator: originator attachment: attachment on:aStream
     "Pricipal logging method. This mimics VM __stxLog__()"
 
-    | messageProperlyEncoded |
+    | facility severityName messageProperlyEncoded words|
 
+    facility := facilityArg.
     messageProperlyEncoded := message.
+    severityName := severity name.
+    
     "/ If the message is Unicode 16/32 string and stream is external,
     "/ we have to recode the message using locale-specific encoding 
     (message isWideString and:[ aStream isExternalStream ]) ifTrue:[ 
@@ -672,26 +762,53 @@
             messageProperlyEncoded := OperatingSystem encodePath: message.
         ]
     ].
-
+    messageProperlyEncoded := messageProperlyEncoded withoutSeparators.
+    
+    "/ hack to allow calls from infPrint/errorPrint.
+    "/ if this is an oldStyle infoPrint or errorPrint, do not append another facility and severity
+    words := message asCollectionOfWords.
+    (words size > 2
+    and:[ words first isAlphaNumeric
+    and:[(words second startsWith:$[ )
+    and:[(words second endsWith:$] ) or:[(words second endsWith:']:' )]]]]) ifTrue:[
+        facility := words first.
+        severityName := words second copyButFirst.
+        severityName := severityName copyTo:(severityName indexOf:$])-1.
+        messageProperlyEncoded := messageProperlyEncoded copyFrom:(messageProperlyEncoded indexOf:$])+1.
+        messageProperlyEncoded := messageProperlyEncoded withoutSeparators.
+        (messageProperlyEncoded startsWith:$:) ifTrue:[
+            messageProperlyEncoded := (messageProperlyEncoded copyFrom:2) withoutSeparators.
+        ].
+    ].
+    
+    "/ Timestamp now printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s.%i'.
+    "/ aStream space.
     aStream
         nextPutAll: facility ? 'STX';
-        space;
-        nextPut:$[;
-        nextPutAll: severity name;
-        nextPut:$];
-        space.
+        nextPutAll:' [';
+        nextPutAll: severityName;
+        nextPutAll:']'.
 
-    aStream nextPut:$(.
+    aStream nextPutAll:' ('.
     Timestamp now printOn:aStream format:'%(year)-%(mon)-%(day) %h:%m:%s.%i'.
-    aStream nextPut:$).
-    aStream space.
-    originator class name printOn: aStream.
-    aStream nextPutAll: ': '.
+    aStream nextPutAll:'): '.
+
     aStream nextPutAll: messageProperlyEncoded.
     aStream cr.
 
     "
      Logger log:'test message' severity: #debug facility: 'TEST'
+     Logger log:'test message' severity: #info facility: 'TEST'
+     Logger log:'test message' severity: #warning facility: 'TEST'
+     Logger log:'test message' severity: #error facility: 'TEST'
+     'test message' infoPrintCR
+     'test message' errorPrintCR
+    "
+    "backward compatibility with infoPrint/errorPrint callers:
+     'foo [info] test message' infoPrintCR
+     'bar [error] test message' errorPrintCR
+     'foo [info]: test message' infoPrintCR
+     'bar [error]: test message' errorPrintCR
     "
 
     "Created: / 14-09-2011 / 21:18:27 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/NoModificationError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/NoModificationError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -11,7 +11,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-ProceedableError subclass:#NoModificationError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#NoModificationError
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -50,7 +52,8 @@
 !NoModificationError class methodsFor:'documentation'!
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/NoModificationError.st,v 1.2 2009-11-05 22:42:42 cg Exp $'
+    ^ '$Header$'
 ! !
 
+
 NoModificationError initialize!
--- a/NonIntegerIndexError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/NonIntegerIndexError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 IndexNotFoundError subclass:#NonIntegerIndexError
     instanceVariableNames: ''
     classVariableNames: ''
@@ -56,7 +58,7 @@
 !NonIntegerIndexError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NonIntegerIndexError.st,v 1.4 2013-04-27 10:04:41 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/NotFoundError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/NotFoundError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -11,7 +11,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-ProceedableError subclass:#NotFoundError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#NotFoundError
     instanceVariableNames: ''
     classVariableNames: ''
     poolDictionaries: ''
@@ -55,7 +57,7 @@
 !NotFoundError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NotFoundError.st,v 1.5 2013-04-27 10:05:48 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/Number.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Number.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -1512,14 +1510,14 @@
 
 maxValue
     "the maximum possible value taking me as a measurement with possible error;
-     as I am exact, thats myself"
+     as I am exact, that's myself"
 
     ^ self
 !
 
 minValue
     "the minimum possible value taking me as a measurement with possible error;
-     as I am exact, thats myself"
+     as I am exact, that's myself"
 
     ^ self
 ! !
--- a/Object.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Object.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -25,7 +23,8 @@
 		KeyNotFoundSignal MessageNotUnderstoodSignal
 		NonIntegerIndexSignal NonWeakDependencies NotFoundSignal
 		OSSignalInterruptSignal ObjectAttributes
-		ObjectAttributesAccessLock PrimitiveFailureSignal
+		ObjectAttributesAccessLock PartialErrorPrintLine
+		PartialInfoPrintLine PrimitiveFailureSignal
 		RecursionInterruptSignal RecursiveStoreStringSignal
 		SubscriptOutOfBoundsSignal SynchronizationSemaphores
 		UserInterruptSignal UserNotificationSignal WarningSignal'
@@ -694,7 +693,6 @@
 ! !
 
 
-
 !Object methodsFor:'accessing'!
 
 _at:index
@@ -1791,6 +1789,8 @@
     "
 ! !
 
+
+
 !Object methodsFor:'attributes access'!
 
 objectAttributeAt:attributeKey
@@ -1918,6 +1918,8 @@
 ! !
 
 
+
+
 !Object methodsFor:'change & update'!
 
 broadcast:aSelectorSymbol
@@ -5301,39 +5303,39 @@
 "/            'Stray recursionInterrupt ...' infoPrintCR.
 "/            ^ self
 "/        ].
-	ObjectMemory infoPrinting ifTrue:[
-	    level := 0.
-	    caller := thisContext sender.
-	    [caller notNil] whileTrue:[
-		level := level + 1.
-		caller := caller sender.
-	    ].
-
-	    'Object [info]: recursionInterrupt from:' printCR.
-	    con := con sender.
-	    remaining := 500.
-	    n := 0.
-	    [con notNil and:[remaining > 0]] whileTrue:[
-		sender := con sender.
-		'| ' print. con fullPrint.
-
-		nSkipped := 0.
-		[sender notNil and:[sender sender notNil
-		and:[sender selector == con selector
-		and:[sender sender selector == con selector
-		and:[sender method == con method]]]]] whileTrue:[
-		    nSkipped := nSkipped + 1.
-		    con := sender.
-		    sender := con sender.
-		].
-		nSkipped > 0 ifTrue:[
-		    '| ... ***** ' print. nSkipped print. ' recursive contexts skipped *****' printCR.
-		].
-		con := sender.
-		remaining := remaining - 1
-	    ].
-	].
-	^ RecursionInterruptSignal raiseSignal
+        ObjectMemory infoPrinting ifTrue:[
+            level := 0.
+            caller := thisContext sender.
+            [caller notNil] whileTrue:[
+                level := level + 1.
+                caller := caller sender.
+            ].
+
+            'Object [info]: recursionInterrupt from:' errorPrintCR.
+            con := con sender.
+            remaining := 500.
+            n := 0.
+            [con notNil and:[remaining > 0]] whileTrue:[
+                sender := con sender.
+                '| ' errorPrint. con fullPrint.
+
+                nSkipped := 0.
+                [sender notNil and:[sender sender notNil
+                and:[sender selector == con selector
+                and:[sender sender selector == con selector
+                and:[sender method == con method]]]]] whileTrue:[
+                    nSkipped := nSkipped + 1.
+                    con := sender.
+                    sender := con sender.
+                ].
+                nSkipped > 0 ifTrue:[
+                    '| ... ***** ' errorPrint. nSkipped errorPrint. ' recursive contexts skipped *****' errorPrintCR.
+                ].
+                con := sender.
+                remaining := remaining - 1
+            ].
+        ].
+        ^ RecursionInterruptSignal raiseSignal
     ]
 
     "Modified: / 10.11.2001 / 15:15:56 / cg"
@@ -7214,16 +7216,21 @@
 !
 
 errorPrint
-    "print the receiver on the Transcript and Stderr.
+    "if a logger has been defined, let it print the receiver when a CR is coming.
+     Otherwise, print the receiver on the Transcript and Stderr.
      The Transcript is directed to the standard error stream on
      headless applications."
 
+    Logger notNil ifTrue:[
+        PartialErrorPrintLine := (PartialErrorPrintLine ? ''),self asString.
+        ^ self.
+    ].
     Stderr isNil ifTrue:[
-	"/ the following allows errorPrint to be used during
-	"/ the early init-phase, when no Stderr has been set up.
-	"/ (depends on string to respond to #errorPrint)
-	self printString utf8Encoded errorPrint.
-	^ self.
+        "/ the following allows errorPrint to be used during
+        "/ the early init-phase, when no Stderr has been set up.
+        "/ (depends on string to respond to #errorPrint)
+        self printString utf8Encoded errorPrint.
+        ^ self.
     ].
 
     self withErrorStreamDo:[:s | self printOn:s].
@@ -7234,16 +7241,24 @@
 errorPrintCR
     "{ Pragma: +optSpace }"
 
-    "print the receiver followed by a cr on the error stream(s).
+    "if a logger has been defined, let it print the receiver.
+     otherwise, print the receiver followed by a cr on the error stream(s).
      The Transcript is directed to the standard error stream on
      headless applications."
 
+    Logger notNil ifTrue:[
+        |fullLine|
+        fullLine := (PartialErrorPrintLine ? ''),self asString.
+        PartialErrorPrintLine := nil.
+        Logger error:fullLine.
+        ^ self.
+    ].
     Stderr isNil ifTrue:[
-	"/ the following allows errorPrintCR to be used during
-	"/ the early init-phase, when no Stderr has been set up.
-	"/ (depends on string to respond to #errorPrintCR)
-	self printString utf8Encoded errorPrintCR.
-	^ self.
+        "/ the following allows errorPrintCR to be used during
+        "/ the early init-phase, when no Stderr has been set up.
+        "/ (depends on string to respond to #errorPrintCR)
+        self printString utf8Encoded errorPrintCR.
+        ^ self.
     ].
 
     self withErrorStreamDo:[:s | self printOn:s. s cr].
@@ -7283,26 +7298,43 @@
 infoPrint
     "{ Pragma: +optSpace }"
 
-    "print the receiver on the standard error stream.
-     This is meant for information messages which are not warnings
-     or fatal messages.
+    "if a logger has been defined, let it print the receiver when a CR is coming.
+     otherwise print the receiver on the standard error stream.
+     This is meant for information messages which are not warnings or fatal messages.
      These messages can be turned on/off by 'Object infoPrinting:true/false'"
 
+    Logger notNil ifTrue:[
+        PartialInfoPrintLine := (PartialInfoPrintLine ? ''),self asString.
+        ^ self.
+    ].
+    
     InfoPrinting == true ifTrue:[
-	self errorPrint
+        self errorPrint
     ]
+
+    "
+     'hello' infoPrint. ' world' infoPrintCR.
+     'foo [info] hello' infoPrintCR.
+    "
 !
 
 infoPrintCR
     "{ Pragma: +optSpace }"
 
-    "print the receiver followed by a cr on the standard error stream.
-     This is meant for information messages which are not warnings
-     or fatal messages.
+    "if a logger has been defined, let it print the receiver.
+     otherwise print the receiver followed by a cr on the standard error stream.
+     This is meant for information messages which are not warnings or fatal messages.
      These messages can be turned on/off by 'Object infoPrinting:true/false'"
 
+    Logger notNil ifTrue:[
+        |fullLine|
+        fullLine := (PartialInfoPrintLine ? ''),self asString.
+        PartialInfoPrintLine := nil.
+        Logger info:fullLine.
+        ^ self.
+    ].
     InfoPrinting == true ifTrue:[
-	self errorPrintCR
+        self errorPrintCR
     ]
 
     "Created: 20.5.1996 / 10:21:28 / cg"
@@ -10447,6 +10479,7 @@
 
 
 
+
 !Object class methodsFor:'documentation'!
 
 version
--- a/ObjectMemory.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ObjectMemory.st	Mon Oct 03 12:44:41 2016 +0100
@@ -795,7 +795,7 @@
 !
 
 current
-    "the 'current' ObjectMemory - thats myself"
+    "the 'current' ObjectMemory - that's myself"
 
     ^ self
 
@@ -2091,7 +2091,7 @@
 checkConsistency
     "call the object memory consistency checker.
      Useful to check if all obejct references are still valid,
-     especially when primitive (inline-C) code is developped.
+     especially when primitive (inline-C) code is developed.
      If called before and after a primitive, missing STORE checks or
      overwritten object headers etc. might be detected.
      (there is no real guarantee, that all such errors are detected, though)"
@@ -3303,6 +3303,14 @@
     self saveGarbageCollectorSetting:#lockTenure: value:flag.
 !
 
+makeOld:anObject
+    "move anObject into oldSpace.
+     This method is for internal & debugging purposes only -
+     it may vanish. Don't use it, unless you know what you are doing."
+
+    ^ self makeOld:anObject now:false
+!
+
 makeOld:anObject now:aBoolean
     "move anObject into oldSpace.
      If aBoolean is true, this is done immediately, but takes some processing time.
@@ -3318,16 +3326,8 @@
     ^ true
 !
 
-makeOld:anObject
-    "move anObject into oldSpace.
-     This method is for internal & debugging purposes only -
-     it may vanish. Don't use it, unless you know what you are doing."
-
-    ^ self makeOld:anObject now:false
-!
-
 maxOldSpace
-    "return the maxOldSpace value. If non-zero, thats the limit for which the
+    "return the maxOldSpace value. If non-zero, that's the limit for which the
      VM will try hard to not allocate more oldSpace memory. (its not a hard limit)
      If zero, it will allocate forever (until the OS wont hand out more).
      The default is zero."
@@ -3344,34 +3344,34 @@
 !
 
 maxOldSpace:amount
-    "set the maxOldSpace value. If non-zero, thats the limit for which the
+    "set the maxOldSpace value. If non-zero, that's the limit for which the
      VM will try hard to not allocate more oldSpace memory. (its not a hard limit)
      If zero, it will allocate forever (until the OS wont hand out more).
      The default is zero.
      WARNING:
-	an oldSpace limit may lead to trashing due to exorbitant GC activity;
-	its usually better to let it allocate more and page in/page out.
-	Usually, the background GC will catch up sooner or later and reclaim
-	the memory without blocking the system"
+        an oldSpace limit may lead to trashing due to exorbitant GC activity;
+        its usually better to let it allocate more and page in/page out.
+        Usually, the background GC will catch up sooner or later and reclaim
+        the memory without blocking the system"
 
     |result|
 %{
     extern unsigned INT __maxOldSpace();
 
     if (__isInteger(amount)) {
-	result = __MKUINT( __maxOldSpace(__unsignedLongIntVal(amount)));
+        result = __MKUINT( __maxOldSpace(__unsignedLongIntVal(amount)));
     }
 %}.
     result notNil ifTrue:[
-	self saveGarbageCollectorSetting:#maxOldSpace: value:amount.
-	^ result.
+        self saveGarbageCollectorSetting:#maxOldSpace: value:amount.
+        ^ result.
     ].
     ^ 0
 
     "
      to change maximum to 1GByte:
 
-	ObjectMemory maxOldSpace:1024*1024*1024
+        ObjectMemory maxOldSpace:1024*1024*1024
     "
 !
 
@@ -3530,7 +3530,7 @@
 !
 
 oldSpaceIncrement
-    "return the oldSpaceIncrement value. Thats the amount by which
+    "return the oldSpaceIncrement value. That's the amount by which
      more memory is allocated in case the oldSpace gets filled up.
      In normal situations, the default value used in the VM is fine
      and there is no need to change it."
@@ -3547,7 +3547,7 @@
 !
 
 oldSpaceIncrement:amount
-    "set the oldSpaceIncrement value. Thats the amount by which
+    "set the oldSpaceIncrement value. That's the amount by which
      more memory is allocated in case the oldSpace gets filled up.
      In normal situations, the default value used in the VM is fine
      and there is no need to change it. This method returns the
@@ -3559,11 +3559,11 @@
     extern unsigned INT __oldSpaceIncrement();
 
     if (__isInteger(amount)) {
-	result = __MKUINT( __oldSpaceIncrement((unsigned INT)__unsignedLongIntVal(amount)) );
+        result = __MKUINT( __oldSpaceIncrement((unsigned INT)__unsignedLongIntVal(amount)) );
     }
 %}.
     result isNil ifTrue:[
-	^ 0.
+        ^ 0.
     ].
     self saveGarbageCollectorSetting:#oldSpaceIncrement: value:amount.
     ^ result.
@@ -5245,7 +5245,7 @@
 !
 
 tenureAge
-    "return the current tenure age - thats the number of times
+    "return the current tenure age - that's the number of times
      an object has to survive scavenges to be moved into oldSpace.
      For statistic/debugging only - this method may vanish"
 
@@ -5799,7 +5799,7 @@
      ST-80 compatibility; send #preSnapshot to all classes
     "
     Smalltalk allClassesDo:[:aClass |
-	aClass preSnapshot
+        aClass preSnapshot
     ].
 
     "
@@ -5809,55 +5809,55 @@
     "
     snapshotFilename := aFileName asFilename.
     snapshotFilename isAbsolute ifFalse:[
-	snapshotFilename := self directoryForImageAndChangeFile
-			    / snapshotFilename name.
+        snapshotFilename := self directoryForImageAndChangeFile
+                            / snapshotFilename name.
     ].
 
     tempFilename := (FileStream newTemporaryIn:snapshotFilename directory)
-			close;
-			fileName.
+                        close;
+                        fileName.
     ok := self primSnapShotOn:tempFilename.
 
     ok ifTrue:[
-	"keep history of one snapshot file"
-	snapshotFilename exists ifTrue:[
-	    tempFilename symbolicAccessRights:snapshotFilename symbolicAccessRights.
-	    snapshotFilename renameTo:(snapshotFilename withSuffix:'sav').
-	] ifFalse:[
-	    "image file hat stx as interpreter and can be executed"
-	    tempFilename makeExecutable.
-	].
-	tempFilename renameTo:snapshotFilename.
-
-	Class addChangeRecordForSnapshot:aFileName.
-
-	setImageName ifTrue:[
-	    oldChangeFile := self nameForChanges.
-	    ImageName := snapshotFilename asAbsoluteFilename asString.
-	    self refreshChangesFrom:oldChangeFile.
-	].
+        "keep history of one snapshot file"
+        snapshotFilename exists ifTrue:[
+            tempFilename symbolicAccessRights:snapshotFilename symbolicAccessRights.
+            snapshotFilename renameTo:(snapshotFilename withSuffix:'sav').
+        ] ifFalse:[
+            "image file has stx as interpreter and can be executed"
+            tempFilename makeExecutable.
+        ].
+        tempFilename renameTo:snapshotFilename.
+
+        Class addChangeRecordForSnapshot:aFileName.
+
+        setImageName ifTrue:[
+            oldChangeFile := self nameForChanges.
+            ImageName := snapshotFilename asAbsoluteFilename asString.
+            self refreshChangesFrom:oldChangeFile.
+        ].
     ] ifFalse:[
-	tempFilename remove.
+        tempFilename remove.
     ].
 
     "
      ST-80 compatibility; send #postSnapshot to all classes
     "
     Smalltalk allClassesDo:[:aClass |
-	aClass postSnapshot
+        aClass postSnapshot
     ].
     self changed:#finishedSnapshot.  "/ ST-80 compatibility
 
     ok ifFalse:[
-	SnapshotError raise.
-	"not reached"
+        SnapshotError raise.
+        "not reached"
     ].
 
     Transcript
-	show:'Snapshot '; show:snapshotFilename baseName allBold;
-	show:' saved '; show:Timestamp now;
-	show:' in '; show:snapshotFilename asAbsoluteFilename directoryName;
-	showCR:'.'.
+        show:'Snapshot '; show:snapshotFilename baseName allBold;
+        show:' saved '; show:Timestamp now;
+        show:' in '; show:snapshotFilename asAbsoluteFilename directoryName;
+        showCR:'.'.
 
     ^ ok
 
--- a/PositionableStream.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/PositionableStream.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -240,7 +242,7 @@
 !
 
 readLimit
-    "return the read-limit; thats the position at which EOF is returned"
+    "return the read-limit; that's the position at which EOF is returned"
 
     ^ readLimit
 
@@ -248,7 +250,7 @@
 !
 
 readLimit:aNumber
-    "set the read-limit; thats the position at which EOF is returned"
+    "set the read-limit; that's the position at which EOF is returned"
 
     readLimit := aNumber
 !
@@ -258,7 +260,7 @@
 !
 
 writeLimit:aNumber
-    "set the writeLimit; thats the position after which writing is prohibited"
+    "set the writeLimit; that's the position after which writing is prohibited"
 
     writeLimit := aNumber
 
--- a/ProjectDefinition.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ProjectDefinition.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -2420,7 +2422,7 @@
     | rules cls processed |
 
     cls := self.
-    rules := String new writeStream.
+    rules := '' writeStream.
     processed := Set new.
     [ cls ~~ Object ] whileTrue:[
         cls class selectorsAndMethodsDo:[:selector :method |
@@ -2769,7 +2771,6 @@
 ! !
 
 
-
 !ProjectDefinition class methodsFor:'description - project information'!
 
 applicationAdditionalIconFileNames
@@ -2968,7 +2969,7 @@
 
     "<major>.<minor>.<revision>.<release> (such as '5.3.2.1')
      the default here takes smalltalks version number.
-     But thats probably not good for an end-user-app."
+     But that's probably not good for an end-user-app."
 
     ^ Smalltalk majorVersionNr
 
@@ -2981,7 +2982,7 @@
 
     "<major>.<minor>.<revision>.<release> (such as '5.3.2.1')
      the default here takes smalltalks version number.
-     But thats probably not good for an end-user-app."
+     But that's probably not good for an end-user-app."
 
     ^ Smalltalk minorVersionNr
 
@@ -3188,7 +3189,7 @@
 
     "<major>.<minor>.<revision>.<release> (such as '5.3.2.1')
      the default here takes smalltalks version number.
-     But thats probably not good for an end-user-app."
+     But that's probably not good for an end-user-app."
 
     ^ Smalltalk releaseNr
 
@@ -3201,7 +3202,7 @@
 
     "<major>.<minor>.<revision>.<release> (such as '5.3.2.1')
      the default here takes smalltalks version number.
-     But thats probably not good for an end-user-app."
+     But that's probably not good for an end-user-app."
 
     ^ Smalltalk revisionNr
 
@@ -4850,7 +4851,6 @@
     ^ self subProjectMakeCallsUsing:'call vcmake %1 %2'.
 ! !
 
-
 !ProjectDefinition class methodsFor:'file templates'!
 
 autopackage_default_dot_apspec
--- a/ReadWriteStream.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ReadWriteStream.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -157,7 +159,7 @@
 !ReadWriteStream methodsFor:'converting'!
 
 readStream
-    "return the receiver as a readStream - thats myself"
+    "return the receiver as a readStream - that's myself"
 
     ^ self
 
@@ -185,7 +187,7 @@
 !ReadWriteStream methodsFor:'queries'!
 
 isReadable 
-    "return true if the receiver supports reading - thats true"
+    "return true if the receiver supports reading - that's true"
 
     ^ true
 !
--- a/Semaphore.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Semaphore.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -512,7 +514,7 @@
 
 setCount:n
     "set the count of the semaphore;
-     thats the number of possible waits, without blocking"
+     that's the number of possible waits, without blocking"
 
     waitingProcesses := nil.
     count := n
@@ -524,7 +526,7 @@
 
 count
     "return the number of 'already-counted' trigger events.
-     Thats the number of waits which will succeed without blocking"
+     That's the number of waits which will succeed without blocking"
 
     ^ count
 
--- a/ShortFloat.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ShortFloat.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1996 by Claus Gittinger
 	      All Rights Reserved
@@ -1346,7 +1348,7 @@
      systems; on SYSV machines you have to give something like %lf,
      while on BSD systems the format string has to be %F.
      Also, the resulting string may not be longer than 255 bytes -
-     since thats the (static) size of the buffer.
+     since that's the (static) size of the buffer.
      This method is NONSTANDARD and may be removed without notice.
      WARNNG: this goes directly to the C-printf function and may therefore me inherently unsafe.
      Please use the printf: method, which is safe as it is completely implemented in Smalltalk."
@@ -1357,23 +1359,23 @@
     int len;
 
     if (__isStringLike(formatString)) {
-	/*
-	 * actually only needed on sparc: since thisContext is
-	 * in a global register, which gets destroyed by printf,
-	 * manually save it here - very stupid ...
-	 */
-	__BEGIN_PROTECT_REGISTERS__
+        /*
+         * actually only needed on sparc: since thisContext is
+         * in a global register, which gets destroyed by printf,
+         * manually save it here - very stupid ...
+         */
+        __BEGIN_PROTECT_REGISTERS__
 
-	len = snprintf(buffer, sizeof(buffer), __stringVal(formatString), __shortFloatVal(self));
+        len = snprintf(buffer, sizeof(buffer), __stringVal(formatString), __shortFloatVal(self));
 
-	__END_PROTECT_REGISTERS__
+        __END_PROTECT_REGISTERS__
 
-	if (len < 0) goto fail;
+        if (len < 0) goto fail;
 
-	s = __MKSTRING_L(buffer, len);
-	if (s != nil) {
-	    RETURN (s);
-	}
+        s = __MKSTRING_L(buffer, len);
+        if (s != nil) {
+            RETURN (s);
+        }
     }
 fail: ;
 %}.
--- a/Signal.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Signal.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -153,7 +155,7 @@
 !Signal class methodsFor:'Signal constants'!
 
 genericSignal
-    "return the generic signal - thats the parent of all signals
+    "return the generic signal - that's the parent of all signals
      in the system."
 
     ^ GenericException
@@ -269,7 +271,7 @@
 
 originalSignal
     "return the signal/exception which was originally raised.
-     For noHandler, that is my unhandled signal; for others, thats the exception itself."
+     For noHandler, that is my unhandled signal; for others, that's the exception itself."
 
     ^ self.
 !
--- a/SignalError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/SignalError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -11,7 +11,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-ProceedableError subclass:#SignalError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#SignalError
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -46,7 +48,7 @@
 !SignalError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SignalError.st,v 1.5 2004/04/22 15:28:24 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/StandaloneStartup.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/StandaloneStartup.st	Mon Oct 03 12:44:41 2016 +0100
@@ -78,7 +78,7 @@
 whichMethodsToRedefine
 "
     main:argv
-        thats the actual program.
+        that's the actual program.
 
     suppressRCFileReading
         false here; redefine to return true, to disable the rc-file reading.
@@ -993,6 +993,9 @@
     idx ~~ 0 ifTrue:[
         argv removeAtIndex:idx.
         Verbose := true.
+        Logger notNil ifTrue:[
+            Logger loggingThreshold: Logger severityALL.
+        ].    
     ].
     self verboseInfo:('args: ',argv asArray printString).
 
--- a/Stream.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Stream.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -631,6 +633,14 @@
      with externalStreams."
 !
 
+lineEndConvention
+     ^ self eolMode
+!
+
+lineEndConvention:aSymbol
+     ^ self eolMode:aSymbol
+!
+
 lineEndLF
     "Ignored here, but added to make internalStreams protocol compatible
      with externalStreams."
@@ -2025,7 +2035,7 @@
 
     "
         (#[] writeStream
-            nextPutAllUtf16Bytes:'BÄxxx' MSB:true;
+            nextPutAllUtf16Bytes:'BÄxxx' MSB:true;
             nextPutUtf16:(Character codePoint:16r10CCCC) MSB:true;
             contents)
    "
@@ -2443,7 +2453,7 @@
     "
         ((WriteStream on:Unicode16String new)
             nextPutUtf16:$B;
-            nextPutUtf16:$Ä; 
+            nextPutUtf16:$Ä; 
             nextPutUtf16:(Character codePoint:16r10CCCC)
             yourself) contents
     "
@@ -2478,13 +2488,13 @@
     "
         (#[] writeStream
             nextPutUtf16:$B MSB:true;
-            nextPutUtf16:$Ä MSB:true;
+            nextPutUtf16:$Ä MSB:true;
             nextPutUtf16:(Character codePoint:16r10CCCC) MSB:true;
             contents)
 
         (FileStream newTemporary
             nextPutUtf16:$B MSB:false;
-            nextPutUtf16:$Ä MSB:false;
+            nextPutUtf16:$Ä MSB:false;
             nextPutUtf16:(Character codePoint:16r10CCCC) MSB:false;
             reset;
             binary;
@@ -2549,7 +2559,7 @@
     "
       (String streamContents:[:s|
             s nextPutUtf8:$a.
-            s nextPutUtf8:$ü.
+            s nextPutUtf8:$ü.
             s nextPutUtf8: (Character value:16r1fff).
             s nextPutUtf8: (Character value:16rffff).
             s nextPutUtf8: (Character value:16r1ffffff).
--- a/String.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/String.st	Mon Oct 03 12:44:41 2016 +0100
@@ -519,6 +519,8 @@
 ! !
 
 
+
+
 !String class methodsFor:'queries'!
 
 defaultPlatformClass
@@ -539,6 +541,10 @@
 ! !
 
 
+
+
+
+
 !String methodsFor:'accessing'!
 
 at:index
@@ -3713,30 +3719,15 @@
 errorPrint
     "print the receiver on standard error, if the global Stderr is nil;
      otherwise, fall back to the inherited errorPrint, which sends the string to
-     the Stderr stream.
-     This method does NOT (by purpose) use the stream classes and
-     will therefore work even in case of emergency during early startup
-     (but only, as long as Stderr is nil, which is set later after startup)."
-
-%{  /* NOCONTEXT */
-#ifdef __SCHTEAM__
-    if (@global(Stderr) == STObject.Nil) {
-	if (self.isStringLike()) {
-	    org.exept.stj.STSystem.err.print(self.asString());
-	    return context._RETURN(self);
-	}
-    }
-#else
-    if (@global(Stderr) == nil) {
-	if (__qIsStringLike(self)) {
-	    console_fprintf(stderr, "%s" , __stringVal(self));
-	    console_fflush(stderr);
-	    RETURN (self);
-	}
-    }
-#endif /* not SCHTEAM */
-%}.
-    super errorPrint
+     the Stderr stream or to a logger.
+     Redefined to be able to print during early startup, when the stream classes have not
+     yet been initialized (Stderr is nil)."
+
+    Stderr isNil ifTrue:[
+        self lowLevelErrorPrint
+    ] ifFalse:[
+        super errorPrint
+    ].    
 
     "
       'hello world' asUnicode16String errorPrint
@@ -3749,84 +3740,138 @@
 errorPrintCR
     "print the receiver on standard error, followed by a cr,
      if the global Stderr is nil; otherwise, fall back to the inherited errorPrintCR,
-     which sends the string to the Stderr stream.
+     which sends the string to the Stderr stream or to a logger.
+     Redefined to be able to print during early startup, when the stream classes have not
+     yet been initialized (Stderr is nil)."
+
+    Stderr isNil ifTrue:[
+        self lowLevelErrorPrintCR
+    ] ifFalse:[
+        super errorPrintCR
+    ].    
+!
+
+lowLevelErrorPrint
+    "Do not call this directly.
+     print the receiver on standard error.
      This method does NOT (by purpose) use the stream classes and
      will therefore work even in case of emergency during early startup
      (but only, as long as Stderr is nil, which is set later after startup)."
 
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
-    if (@global(Stderr) == STObject.Nil) {
-	if (self.isStringLike()) {
-	    org.exept.stj.STSystem.err.println(self.asString());
-	    return context._RETURN(self);
-	}
+    if (self.isStringLike()) {
+        org.exept.stj.STSystem.err.print(self.asString());
+        return context._RETURN(self);
     }
 #else
-    if (@global(Stderr) == nil) {
-	if (__qIsStringLike(self)) {
-	    console_fprintf(stderr, "%s\n" , __stringVal(self));
-	    console_fflush(stderr);
-	    RETURN (self);
-	}
+    if (__qIsStringLike(self)) {
+        console_fprintf(stderr, "%s" , __stringVal(self));
+        console_fflush(stderr);
+        RETURN (self);
+    }
+#endif /* not SCHTEAM */
+%}.
+
+    "
+      'hello world' asUnicode16String errorPrint
+      (Character value:356) asString errorPrint
+      'Bönnigheim' errorPrint
+      'Bönnigheim' asUnicodeString errorPrint
+    "
+!
+
+lowLevelErrorPrintCR
+    "Do not call this directly.
+     print the receiver on standard error, followed by a cr,
+     This method does NOT (by purpose) use the stream classes and
+     will therefore work even in case of emergency during early startup
+     (but only, as long as Stderr is nil, which is set later after startup)."
+
+%{  /* NOCONTEXT */
+#ifdef __SCHTEAM__
+    if (self.isStringLike()) {
+        org.exept.stj.STSystem.err.println(self.asString());
+        return context._RETURN(self);
+    }
+#else
+    if (__qIsStringLike(self)) {
+        console_fprintf(stderr, "%s\n" , __stringVal(self));
+        console_fflush(stderr);
+        RETURN (self);
     }
 #endif
 %}.
-    super errorPrintCR
 !
 
-print
-    "print the receiver on standard output, if the global Stdout is nil;
-     otherwise, fall back to the inherited print,
-     which sends the string to the Stdout stream.
+lowLevelPrint
+    "Do not call this directly.
+     print the receiver on standard output.
      This method does NOT (by purpose) use the stream classes and
      will therefore work even in case of emergency during early startup
      (but only, as long as Stdout is nil, which is set later after startup)."
 
 %{  /* NOCONTEXT */
 #ifdef __SCHTEAM__
-    if (STSmalltalkEnvironment.GetBindingOrNull(STSymbol._new("Stdout")) == null) {
-	org.exept.stj.STSystem.out.print(self.toString());
-	return context._RETURN(self);
-    }
+    org.exept.stj.STSystem.out.print(self.toString());
+    return context._RETURN(self);
 #else
-    if (@global(Stdout) == nil) {
-	if (__qIsStringLike(self)) {
-	    console_fprintf(stdout, "%s" , __stringVal(self));
-	    console_fflush(stdout);
-	    RETURN (self);
-	}
+    if (__qIsStringLike(self)) {
+        console_fprintf(stdout, "%s" , __stringVal(self));
+        console_fflush(stdout);
+        RETURN (self);
     }
 #endif
 %}.
-    super print
+!
+
+lowLevelPrintCR
+    "Do not call this directly.
+     print the receiver on standard output, followed by a cr,
+     This method does NOT (by purpose) use the stream classes and
+     will therefore work even in case of emergency during early startup
+     (but only, as long as Stdout is nil, which is set later after startup)."
+
+%{  /* NOCONTEXT */
+#ifdef __SCHTEAM__
+    org.exept.stj.STSystem.out.println(self.toString());
+    return context._RETURN(self);
+#else
+    if (__qIsStringLike(self)) {
+        console_fprintf(stdout, "%s\n" , __stringVal(self));
+        console_fflush(stdout);
+        RETURN (self);
+    }
+#endif
+%}.
+!
+
+print
+    "print the receiver on standard output, if the global Stdout is nil;
+     otherwise, fall back to the inherited print,
+     which sends the string to the Stdout stream.
+     Redefined to be able to print during early startup, when the stream classes have not
+     yet been initialized (Stdout is nil)."
+
+    Stdout isNil ifTrue:[
+        self lowLevelPrint
+    ] ifFalse:[
+        super print
+    ].    
 !
 
 printCR
     "print the receiver on standard output, followed by a cr,
      if the global Stdout is nil; otherwise, fall back to the inherited errorPrintCR,
      which sends the string to the Stdout stream.
-     This method does NOT (by purpose) use the stream classes and
-     will therefore work even in case of emergency during early startup
-     (but only, as long as Stdout is nil, which is set later after startup)."
-
-%{  /* NOCONTEXT */
-#ifdef __SCHTEAM__
-    if (STSmalltalkEnvironment.GetBindingOrNull(STSymbol._new("Stdout")) == null) {
-	org.exept.stj.STSystem.out.println(self.toString());
-	return context._RETURN(self);
-    }
-#else
-    if (@global(Stdout) == nil) {
-	if (__qIsStringLike(self)) {
-	    console_fprintf(stdout, "%s\n" , __stringVal(self));
-	    console_fflush(stdout);
-	    RETURN (self);
-	}
-    }
-#endif
-%}.
-    super printCR
+     Redefined to be able to print during early startup, when the stream classes have not
+     yet been initialized (Stdout is nil)."
+
+    Stdout isNil ifTrue:[
+        self lowLevelPrintCR
+    ] ifFalse:[
+        super printCR
+    ].    
 !
 
 printfPrintString:formatString
@@ -4220,6 +4265,7 @@
     ^ super reverse
 ! !
 
+
 !String methodsFor:'substring searching'!
 
 indexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:caseSensitive
@@ -4896,6 +4942,7 @@
 
 ! !
 
+
 !String class methodsFor:'documentation'!
 
 version
--- a/StringCollection.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/StringCollection.st	Mon Oct 03 12:44:41 2016 +0100
@@ -38,7 +38,7 @@
 
 documentation
 "
-    StringCollection is an variable sized array of lines which are strings.
+    StringCollection is a variable sized array of lines which are strings.
     WARNING:
         This class is temporary (a historic leftover) - it may change or
         even vanish in the future. Use OrderedCollections or other standard
--- a/SubclassResponsibilityError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/SubclassResponsibilityError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2001 by eXept Software AG
               All Rights Reserved
@@ -15,7 +13,7 @@
 
 "{ NameSpace: Smalltalk }"
 
-ProceedableError subclass:#SubclassResponsibilityError
+ExecutionError subclass:#SubclassResponsibilityError
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
--- a/TimeDuration.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/TimeDuration.st	Mon Oct 03 12:44:41 2016 +0100
@@ -658,7 +658,7 @@
 !
 
 asTimeDuration
-    "return a TimeDuration object from the receiver - thats the receiver."
+    "return a TimeDuration object from the receiver - that's the receiver."
 
     ^ self
 ! !
--- a/Timestamp.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Timestamp.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1567,10 +1567,10 @@
             'NFT'   690 false          "/ norfolk island, australia
 
             'CHAST' 765 false          "/ chatham island standard
-            'WST'   780 false          "/ west samoa - yes thats 13!!
-            'TOT'   780 false          "/ tonga - yes thats 13!!
-            'TKT'   780 false          "/ tokelau - yes thats 13!!
-            'LINT'  840 false          "/ line islands - yes thats 14!!
+            'WST'   780 false          "/ west samoa - yes that's 13!!
+            'TOT'   780 false          "/ tonga - yes that's 13!!
+            'TKT'   780 false          "/ tokelau - yes that's 13!!
+            'LINT'  840 false          "/ line islands - yes that's 14!!
 
             "/ misc
             'IDLW' -720 false          "/ international date line west
--- a/UnimplementedFunctionalityError.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/UnimplementedFunctionalityError.st	Mon Oct 03 12:44:41 2016 +0100
@@ -11,7 +11,9 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-ProceedableError subclass:#UnimplementedFunctionalityError
+"{ NameSpace: Smalltalk }"
+
+ExecutionError subclass:#UnimplementedFunctionalityError
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -62,13 +64,14 @@
 !UnimplementedFunctionalityError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UnimplementedFunctionalityError.st,v 1.2 2006/03/03 19:13:11 stefan Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
     ^ '$Id: UnimplementedFunctionalityError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
+
 UnimplementedFunctionalityError initialize!
 
 
--- a/UnixOperatingSystem.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/UnixOperatingSystem.st	Mon Oct 03 12:44:41 2016 +0100
@@ -3785,13 +3785,14 @@
     |info path|
 
     "shortcut - use the /proc filesystem (if present).
-     Here we get an absolute path to the running executable."
+     Here we get an absolute path to the running executable.
+     Notice: we cannot depend on /proc to be present (actually only is on linux)"
     info := '/proc/self/exe' asFilename linkInfo.
     info notNil ifTrue:[
-	path := info path.
-	path notEmptyOrNil ifTrue:[
-	    ^ path
-	].
+        path := info path.
+        path notEmptyOrNil ifTrue:[
+            ^ path
+        ].
      ].
 
     "Fall back - do it the hard way"
@@ -3804,43 +3805,52 @@
 !
 
 pathOfCommand:aCommand
-    "find where aCommand's executable file is;
-     return its full pathName if there is such a command, otherwise
-     return nil."
+    "find where aCommand's executable file would be searched for if executed by a shell.
+     Return nil if aCommand is either absolute, or relative and not executable,
+     or not executable is found along the PATH."
 
     |path f fExt commandFilename|
 
     commandFilename := aCommand asFilename.
     commandFilename isAbsolute ifTrue:[
-	^ commandFilename pathName
+        "/ something like "/foo/...", tried path is it
+        commandFilename isExecutable ifFalse:[^ nil].
+        ^ commandFilename pathName
     ].
     commandFilename isExplicitRelative ifTrue:[
-	 ^ commandFilename pathName
+        "/ something like "../foo/...", tried path resolved relative to the current directory
+        commandFilename isExecutable ifFalse:[^ nil].
+         ^ commandFilename pathName
     ].
     (aCommand includes:$/) ifTrue:[
-	"/ something like "smalltalk/stx", if executed from a parent directory
-	^ ('./',aCommand) asFilename pathName
-    ].
-
+        "/ something like "smalltalk/stx", tried path is relative to the current directory
+        (f := ('./',aCommand) asFilename) isExecutable ifTrue:[
+            ^ f pathName
+        ].    
+        ^ nil
+    ].
+
+    "/ command is a single word, not relative and not absolute.
+    "/ search along PATH environment variable to see what a shoell would do.
     path := self getEnvironment:'PATH'.
     path notEmptyOrNil ifTrue:[
-	(path asCollectionOfSubstringsSeparatedBy:self pathSeparator) do:[:eachPathComponent |
-	    eachPathComponent isEmpty ifTrue:[
-		f := commandFilename
-	    ] ifFalse:[
-		f := eachPathComponent asFilename construct:aCommand.
-	    ].
-	    self executableFileExtensions do:[:eachExtension |
-		eachExtension notEmpty ifTrue:[
-		    fExt := f addSuffix:eachExtension.
-		] ifFalse:[
-		    fExt := f.
-		].
-		fExt isExecutable ifTrue:[
-		    ^ fExt pathName
-		].
-	    ].
-	].
+        (path asCollectionOfSubstringsSeparatedBy:self pathSeparator) do:[:eachPathComponent |
+            eachPathComponent isEmpty ifTrue:[
+                f := commandFilename
+            ] ifFalse:[
+                f := eachPathComponent asFilename construct:aCommand.
+            ].
+            self executableFileExtensions do:[:eachExtension |
+                eachExtension notEmpty ifTrue:[
+                    fExt := f addSuffix:eachExtension.
+                ] ifFalse:[
+                    fExt := f.
+                ].
+                fExt isExecutable ifTrue:[
+                    ^ fExt pathName
+                ].
+            ].
+        ].
     ].
     ^ nil
 
@@ -5722,7 +5732,7 @@
 
 pathNameOf:pathName
     "return the pathName of the argument, aPathString,
-     - thats the full pathname of the directory, starting at '/'.
+     - that's the full pathname of the directory, starting at '/'.
      This method needs the path to be valid
      (i.e. all directories must exist, be readable and executable).
      Notice: if symbolic links are involved, the result may look different
@@ -5731,66 +5741,66 @@
     |p path command|
 
     path = '.' ifTrue:[
-	^ self getCurrentDirectory.
+        ^ self getCurrentDirectory.
     ].
 
     "some systems have a convenient function for this ..."
     path := self primPathNameOf:(self encodePath:pathName).
     path notNil ifTrue:[
-	path := self decodePath:path.
+        path := self decodePath:path.
     ] ifFalse:[
-	(self isValidPath:pathName) ifFalse:[
-	    p := pathName.
-	    [(p size > 1)
-	     and:[p endsWith:(self fileSeparator)]
-	    ] whileTrue:[
-		p := p copyButLast.
-	    ].
-	    ^ p
-	].
-
-	(SlowFork==true or:[PipeFailed==true]) ifFalse:[
-	    |directoryName fileBaseName|
-
-	    (self isDirectory:pathName) ifTrue:[
-		directoryName := pathName.
-		fileBaseName := nil.
-	    ] ifFalse:[
-		|pathFilename|
-		pathFilename := pathName asFilename.
-		directoryName := pathFilename directoryName.
-		fileBaseName := pathFilename baseName.
-	    ].
-
-	    PipeStream openErrorSignal handle:[:ex |
-		PipeFailed := true.
-		'UnixOperatingSystem [warning]: cannot fork/popen' errorPrintCR.
-		ex return.
-	    ] do:[
-		"have to fall back ..."
-		command := 'cd "' , directoryName , '"; pwd'.
-		p := PipeStream readingFrom:command.
-	    ].
-
-	    (p isNil or:[p atEnd]) ifTrue:[
-		('UnixOperatingSystem [warning]: PipeStream for <' , command , '> failed') errorPrintCR.
-	    ] ifFalse:[
-		path := p nextLine.
-		p close.
-	    ].
-	    fileBaseName notNil ifTrue:[
-		path := path, '/', fileBaseName.
-	    ].
-	].
-	path isNil ifTrue:[
-	    "/
-	    "/ return the original - there is nothing else can we do
-	    "/
-	    path := pathName
-	].
-	(SlowFork==true or:[ForkFailed==true]) ifTrue:[
-	    path := self compressPath:path
-	]
+        (self isValidPath:pathName) ifFalse:[
+            p := pathName.
+            [(p size > 1)
+             and:[p endsWith:(self fileSeparator)]
+            ] whileTrue:[
+                p := p copyButLast.
+            ].
+            ^ p
+        ].
+
+        (SlowFork==true or:[PipeFailed==true]) ifFalse:[
+            |directoryName fileBaseName|
+
+            (self isDirectory:pathName) ifTrue:[
+                directoryName := pathName.
+                fileBaseName := nil.
+            ] ifFalse:[
+                |pathFilename|
+                pathFilename := pathName asFilename.
+                directoryName := pathFilename directoryName.
+                fileBaseName := pathFilename baseName.
+            ].
+
+            PipeStream openErrorSignal handle:[:ex |
+                PipeFailed := true.
+                'UnixOperatingSystem [warning]: cannot fork/popen' errorPrintCR.
+                ex return.
+            ] do:[
+                "have to fall back ..."
+                command := 'cd "' , directoryName , '"; pwd'.
+                p := PipeStream readingFrom:command.
+            ].
+
+            (p isNil or:[p atEnd]) ifTrue:[
+                ('UnixOperatingSystem [warning]: PipeStream for <' , command , '> failed') errorPrintCR.
+            ] ifFalse:[
+                path := p nextLine.
+                p close.
+            ].
+            fileBaseName notNil ifTrue:[
+                path := path, '/', fileBaseName.
+            ].
+        ].
+        path isNil ifTrue:[
+            "/
+            "/ return the original - there is nothing else can we do
+            "/
+            path := pathName
+        ].
+        (SlowFork==true or:[ForkFailed==true]) ifTrue:[
+            path := self compressPath:path
+        ]
     ].
     ^ path.
 
@@ -5872,7 +5882,7 @@
 
 primPathNameOf:pathName
     "return the pathName of the argument, aPathString,
-     - thats the full pathname of the directory, starting at '/'.
+     - that's the full pathname of the directory, starting at '/'.
      This method here returns nil, if the OS does not provide a
      realPath library function.
      Notice: if symbolic links are involved, the result may look different
@@ -5883,30 +5893,30 @@
 %{  /* UNLIMITEDSTACK */
 #ifdef __SCHTEAM__
     if (pathName.isStringLike()) {
-	java.io.File file = new java.io.File( pathName.asString() );
-
-	if (file.exists()) {
-	    return __c__._RETURN( new STString( file.getAbsolutePath() ));
-	}
+        java.io.File file = new java.io.File( pathName.asString() );
+
+        if (file.exists()) {
+            return __c__._RETURN( new STString( file.getAbsolutePath() ));
+        }
     }
 #else
     if (__isStringLike(pathName)) {
 # ifdef HAS_REALPATH
-	extern char *realpath();
-
-	// POSIX-2008 says, that a NULL namebuffer causes realPath to malloc()
-	// the required memory. But this does not work as of 2013-04
-	char nameBuffer[MAXPATHLEN+1];
-	char *nameP = realpath(__stringVal(pathName), nameBuffer);
-	if (nameP) {
-	    OBJ ret = __MKSTRING(nameP);
-	    // free(nameP);
-	    RETURN ( ret );
-	}
-	// fprintf(stderr, "stx[warning]: realpath(\"%s\") failed: %s\n", __stringVal(pathName), strerror(errno));
+        extern char *realpath();
+
+        // POSIX-2008 says, that a NULL namebuffer causes realPath to malloc()
+        // the required memory. But this does not work as of 2013-04
+        char nameBuffer[MAXPATHLEN+1];
+        char *nameP = realpath(__stringVal(pathName), nameBuffer);
+        if (nameP) {
+            OBJ ret = __MKSTRING(nameP);
+            // free(nameP);
+            RETURN ( ret );
+        }
+        // fprintf(stderr, "stx[warning]: realpath(\"%s\") failed: %s\n", __stringVal(pathName), strerror(errno));
 # endif /* ! HAS_REALPATH */
     } else {
-	error = @symbol(argument);     // argument is not a string
+        error = @symbol(argument);     // argument is not a string
     }
 #endif
 %}.
@@ -5917,9 +5927,9 @@
     ^ nil
 
     "
-	self primPathNameOf:'.'
-	self primPathNameOf:'/murks/quatsch/bla/.'
-	self primPathNameOf:5555
+        self primPathNameOf:'.'
+        self primPathNameOf:'/murks/quatsch/bla/.'
+        self primPathNameOf:5555
     "
 !
 
@@ -6085,7 +6095,7 @@
 
 volumeNameOf:aPathString
     "return the volumeName of the argument, aPath
-     - thats the name of the volume where aPath is.
+     - that's the name of the volume where aPath is.
      Not all OperatingSystems support/use volumes; on unix,
      this always returns an empty string."
 
@@ -10554,7 +10564,7 @@
 getEffectiveGroupID
     "{ Pragma: +optSpace }"
 
-    "return the current users (thats you) effective numeric group id.
+    "return the current users (that's you) effective numeric group id.
      This is only different from getGroupID, if you have ST/X running
      as a setuid program (of which you should think about twice)."
 
@@ -10573,7 +10583,7 @@
 getEffectiveUserID
     "{ Pragma: +optSpace }"
 
-    "return the current users (thats you) effective numeric user id.
+    "return the current users (that's you) effective numeric user id.
      This is only different from getUserID, if you have ST/X running
      as a setuid program (of which you should think about twice)."
 
@@ -10619,7 +10629,7 @@
 !
 
 getGroupID
-    "return the current users (thats you) numeric group id"
+    "return the current users (that's you) numeric group id"
 
     "{ Pragma: +optSpace }"
 
@@ -10683,7 +10693,7 @@
 getLoginName
     "{ Pragma: +optSpace }"
 
-    "return a string with the users login name (thats yours)"
+    "return a string with the users login name (that's yours)"
 
 %{  /* NOCONTEXT */
     static char cachedName[128];
@@ -10694,32 +10704,32 @@
     char *name = (char *)0;
 
     if (firstCall) {
-	/*
-	 * try a few common environment variables ...
-	 */
-	name = getenv("LOGNAME");
-	if (! name || (name[0] == 0)) {
-	    name = getlogin();
-	    if (! name || (name[0] == 0) ) {
-		name = getenv("LOGIN");
-		if (! name || (name[0] == 0) ) {
-		    name = getenv("USER");
-		}
-	    }
-	}
-	if (name && (strlen(name) < sizeof(cachedName))) {
-	    strcpy(cachedName, name);
-	    firstCall = 0;
-	}
+        /*
+         * try a few common environment variables ...
+         */
+        name = getenv("LOGNAME");
+        if (! name || (name[0] == 0)) {
+            name = getlogin();
+            if (! name || (name[0] == 0) ) {
+                name = getenv("LOGIN");
+                if (! name || (name[0] == 0) ) {
+                    name = getenv("USER");
+                }
+            }
+        }
+        if (name && (strlen(name) < sizeof(cachedName))) {
+            strcpy(cachedName, name);
+            firstCall = 0;
+        }
     } else {
-	name = cachedName;
+        name = cachedName;
     }
 
     /*
      * nope - I really dont know who you are.
      */
     if (! name || (name[0] == 0) ) {
-	name = "you";
+        name = "you";
     }
 
     RETURN ( __MKSTRING(name) );
@@ -10730,7 +10740,7 @@
 !
 
 getUserID
-    "return the current users (thats you) numeric user id"
+    "return the current users (that's you) numeric user id"
 
     "{ Pragma: +optSpace }"
 
--- a/Win32OperatingSystem.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/Win32OperatingSystem.st	Mon Oct 03 12:44:41 2016 +0100
@@ -17,211 +17,211 @@
 "{ NameSpace: Smalltalk }"
 
 AbstractOperatingSystem subclass:#Win32OperatingSystem
-        instanceVariableNames:''
-        classVariableNames:'Initialized HostName DomainName CurrentDirectory LastOsTimeLow
-                LastOsTimeHi LastTimeInfoIsLocal LastTimeInfo'
-        poolDictionaries:'Win32Constants'
-        category:'OS-Windows'
+	instanceVariableNames:''
+	classVariableNames:'Initialized HostName DomainName CurrentDirectory LastOsTimeLow
+		LastOsTimeHi LastTimeInfoIsLocal LastTimeInfo'
+	poolDictionaries:'Win32Constants'
+	category:'OS-Windows'
 !
 
 ByteArray variableByteSubclass:#DevModeStructure
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 ByteArray variableByteSubclass:#DocInfoStructure
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Object subclass:#FileStatusInfo
-        instanceVariableNames:'type mode uid gid size id accessed modified created statusChanged
-                sourcePath linkTargetPath fullPathName alternativePathName'
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:'type mode uid gid size id accessed modified created statusChanged
+		sourcePath linkTargetPath fullPathName alternativePathName'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Object subclass:#OSProcessStatus
-        instanceVariableNames:'pid status code core'
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:'pid status code core'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 SharedPool subclass:#PECOFFConstants
-        instanceVariableNames:''
-        classVariableNames:'PE_Signature_OFFSET_OFFSET PE_Signature COFF_HEADER_SIZE
-                COFF_HEADER_Machine_OFFSET IMAGE_FILE_MACHINE_UNKNOWN
-                IMAGE_FILE_MACHINE_AM33 IMAGE_FILE_MACHINE_AMD64
-                IMAGE_FILE_MACHINE_ARM IMAGE_FILE_MACHINE_ARMNT
-                IMAGE_FILE_MACHINE_ARM64 IMAGE_FILE_MACHINE_EBC
-                IMAGE_FILE_MACHINE_I386 IMAGE_FILE_MACHINE_IA64
-                IMAGE_FILE_MACHINE_M32R IMAGE_FILE_MACHINE_MIPS16
-                IMAGE_FILE_MACHINE_MIPSFPU IMAGE_FILE_MACHINE_MIPSFPU16
-                IMAGE_FILE_MACHINE_POWERPC IMAGE_FILE_MACHINE_POWEPCFP
-                IMAGE_FILE_MACHINE_R4000 IMAGE_FILE_MACHINE_SH3
-                IMAGE_FILE_MACHINE_SH3DSP IMAGE_FILE_MACHINE_SH4
-                IMAGE_FILE_MACHINE_SH5 IMAGE_FILE_MACHINE_THUMB
-                IMAGE_FILE_MACHINE_WCEMIPSV2'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:'PE_Signature_OFFSET_OFFSET PE_Signature COFF_HEADER_SIZE
+		COFF_HEADER_Machine_OFFSET IMAGE_FILE_MACHINE_UNKNOWN
+		IMAGE_FILE_MACHINE_AM33 IMAGE_FILE_MACHINE_AMD64
+		IMAGE_FILE_MACHINE_ARM IMAGE_FILE_MACHINE_ARMNT
+		IMAGE_FILE_MACHINE_ARM64 IMAGE_FILE_MACHINE_EBC
+		IMAGE_FILE_MACHINE_I386 IMAGE_FILE_MACHINE_IA64
+		IMAGE_FILE_MACHINE_M32R IMAGE_FILE_MACHINE_MIPS16
+		IMAGE_FILE_MACHINE_MIPSFPU IMAGE_FILE_MACHINE_MIPSFPU16
+		IMAGE_FILE_MACHINE_POWERPC IMAGE_FILE_MACHINE_POWEPCFP
+		IMAGE_FILE_MACHINE_R4000 IMAGE_FILE_MACHINE_SH3
+		IMAGE_FILE_MACHINE_SH3DSP IMAGE_FILE_MACHINE_SH4
+		IMAGE_FILE_MACHINE_SH5 IMAGE_FILE_MACHINE_THUMB
+		IMAGE_FILE_MACHINE_WCEMIPSV2'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Object subclass:#PECOFFFileHeader
-        instanceVariableNames:'file data'
-        classVariableNames:''
-        poolDictionaries:'Win32OperatingSystem::PECOFFConstants'
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:'file data'
+	classVariableNames:''
+	poolDictionaries:'Win32OperatingSystem::PECOFFConstants'
+	privateIn:Win32OperatingSystem
 !
 
 Object subclass:#PerformanceData
-        instanceVariableNames:'objectArray perfTime perfFreq perfTime100nSec'
-        classVariableNames:'PerformanceText CounterIndexTextDictionary
-                HelpIndexTextDictionary'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:'objectArray perfTime perfFreq perfTime100nSec'
+	classVariableNames:'PerformanceText CounterIndexTextDictionary
+		HelpIndexTextDictionary'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Object subclass:#Abstract
-        instanceVariableNames:'lastData lastTimestamp cachedResults'
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem::PerformanceData
+	instanceVariableNames:'lastData lastTimestamp cachedResults'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem::PerformanceData
 !
 
 Win32OperatingSystem::PerformanceData::Abstract subclass:#DiskIO
-        instanceVariableNames:''
-        classVariableNames:'TheOneAndOnlyInstance'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem::PerformanceData
+	instanceVariableNames:''
+	classVariableNames:'TheOneAndOnlyInstance'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem::PerformanceData
 !
 
 Win32OperatingSystem::PerformanceData::Abstract subclass:#Global
-        instanceVariableNames:''
-        classVariableNames:'TheOneAndOnlyInstance'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem::PerformanceData
+	instanceVariableNames:''
+	classVariableNames:'TheOneAndOnlyInstance'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem::PerformanceData
 !
 
 Win32OperatingSystem::PerformanceData::Abstract subclass:#Memory
-        instanceVariableNames:''
-        classVariableNames:'TheOneAndOnlyInstance'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem::PerformanceData
+	instanceVariableNames:''
+	classVariableNames:'TheOneAndOnlyInstance'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem::PerformanceData
 !
 
 Win32OperatingSystem::PerformanceData::Abstract subclass:#Network
-        instanceVariableNames:''
-        classVariableNames:'TheOneAndOnlyInstance'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem::PerformanceData
+	instanceVariableNames:''
+	classVariableNames:'TheOneAndOnlyInstance'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem::PerformanceData
 !
 
 Win32OperatingSystem::PerformanceData::Abstract subclass:#Process
-        instanceVariableNames:''
-        classVariableNames:'TheOneAndOnlyInstance'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem::PerformanceData
+	instanceVariableNames:''
+	classVariableNames:'TheOneAndOnlyInstance'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem::PerformanceData
 !
 
 Win32OperatingSystem::PerformanceData::Abstract subclass:#Processor
-        instanceVariableNames:''
-        classVariableNames:'TheOneAndOnlyInstance'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem::PerformanceData
+	instanceVariableNames:''
+	classVariableNames:'TheOneAndOnlyInstance'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem::PerformanceData
 !
 
 ByteArray variableByteSubclass:#PrinterInfo2Structure
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Object subclass:#RegistryEntry
-        instanceVariableNames:'path handle isNew'
-        classVariableNames:'Lobby HKEY_CLASSES_ROOT HKEY_CURRENT_USER HKEY_LOCAL_MACHINE
-                HKEY_USERS HKEY_PERFORMANCE_DATA HKEY_CURRENT_CONFIG
-                HKEY_DYN_DATA HKEY_PERFORMANCE_TEXT HKEY_PERFORMANCE_NLSTEXT'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:'path handle isNew'
+	classVariableNames:'Lobby HKEY_CLASSES_ROOT HKEY_CURRENT_USER HKEY_LOCAL_MACHINE
+		HKEY_USERS HKEY_PERFORMANCE_DATA HKEY_CURRENT_CONFIG
+		HKEY_DYN_DATA HKEY_PERFORMANCE_TEXT HKEY_PERFORMANCE_NLSTEXT'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 ByteArray variableByteSubclass:#TextMetricsStructure
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Win32Handle subclass:#Win32ChangeNotificationHandle
-        instanceVariableNames:''
-        classVariableNames:'Lobby'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:'Lobby'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Win32Handle subclass:#Win32IOHandle
-        instanceVariableNames:''
-        classVariableNames:'Lobby'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:'Lobby'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Win32Handle subclass:#Win32NetworkResourceHandle
-        instanceVariableNames:''
-        classVariableNames:'ScopeMappingTable TypeMappingTable DisplayTypeMappingTable
-                UsageMappingTable'
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:'ScopeMappingTable TypeMappingTable DisplayTypeMappingTable
+		UsageMappingTable'
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Object subclass:#NetworkResource
-        instanceVariableNames:'scope type usage displayType remoteName localName provider
-                comment'
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem::Win32NetworkResourceHandle
+	instanceVariableNames:'scope type usage displayType remoteName localName provider
+		comment'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem::Win32NetworkResourceHandle
 !
 
 Win32Handle subclass:#Win32PrinterHandle
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Win32Handle subclass:#Win32ProcessHandle
-        instanceVariableNames:'pid'
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:'pid'
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Win32OperatingSystem::Win32IOHandle subclass:#Win32SerialPortHandle
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 Win32OperatingSystem::Win32IOHandle subclass:#Win32SocketHandle
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 ByteArray variableByteSubclass:#WinPointStructure
-        instanceVariableNames:''
-        classVariableNames:''
-        poolDictionaries:''
-        privateIn:Win32OperatingSystem
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	privateIn:Win32OperatingSystem
 !
 
 !Win32OperatingSystem primitiveDefinitions!
@@ -568,7 +568,31 @@
 
 !Win32OperatingSystem primitiveFunctions!
 %{
-#define __wait wait
+int
+_makeWchar(OBJ string, wchar_t *buffer, int bufferSize)
+{
+    int i, len;
+
+    if (__isStringLike(string)) {
+        len = __stringSize(string);
+        if (len > bufferSize) len = bufferSize;
+        for (i=0; i<len; i++) {
+            buffer[i] = __stringVal(string)[i];
+        }
+    } else if (__isUnicode16String(string)) {
+        len = __unicode16StringSize(string);
+        if (len > bufferSize) len = bufferSize;
+        for (i=0; i<len; i++) {
+            buffer[i] = __unicode16StringVal(string)[i];
+        }
+    } else {
+        return(-1);
+    }
+    buffer[len] = 0;
+    return(len);
+}
+
+
 
 static int
 _canAccessIOWithoutBlocking (HANDLE handle, int readMode)
@@ -4638,15 +4662,8 @@
     if (__isUnicode16String(aPathName)) {
         int ret;
         wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
-
+
+        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
         ret = CreateDirectoryW(_wPathName, &sa);
         if (ret != TRUE) {
             __threadErrno = __WIN32_ERR(GetLastError());
@@ -4825,12 +4842,7 @@
     if (__isStringLike(pathName)) {
         name = __stringVal(pathName);
     } else if (__isUnicode16String(pathName)) {
-        l = __unicode16StringSize(pathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(pathName)[i];
-        }
-        _wPathName[i] = 0;
+        _makeWchar(pathName, _wPathName, sizeof(_wPathName));
     } else {
         fileHandle = nil;
         argumentError = @symbol(badPathName);
@@ -4986,19 +4998,12 @@
             RETURN (false);
         }
         RETURN (true);
-    }
-    if (__isUnicode16String(fullPathName)) {
+    } else if (__isUnicode16String(fullPathName)) {
 #ifdef DO_WRAP_CALLS
         {
             wchar_t _wPathName[MAXPATHLEN+1];
-            int i, l;
-
-            l = __unicode16StringSize(fullPathName);
-            if (l > MAXPATHLEN) l = MAXPATHLEN;
-            for (i=0; i<l; i++) {
-                _wPathName[i] = __unicode16StringVal(fullPathName)[i];
-            }
-            _wPathName[i] = 0;
+
+            _makeWchar(fullPathName, _wPathName, sizeof(_wPathName));
             do {
                 __threadErrno = 0;
                 // do not cast to INT - will loose sign bit then!
@@ -5006,7 +5011,7 @@
             } while ((ret < 0) && (__threadErrno == EINTR));
         }
 #else
-        ret = RemoveDirectoryW((char *)__stringVal(fullPathName));
+        ret = RemoveDirectoryW((wchar_t *)__unicode16StringVal(fullPathName));
         __threadErrno = __WIN32_ERR(GetLastError());
 #endif
         if (ret != TRUE) {
@@ -5061,14 +5066,8 @@
 #ifdef DO_WRAP_CALLS
         {
             wchar_t _wPathName[MAXPATHLEN+1];
-            int i, l;
-
-            l = __unicode16StringSize(fullPathName);
-            if (l > MAXPATHLEN) l = MAXPATHLEN;
-            for (i=0; i<l; i++) {
-                _wPathName[i] = __unicode16StringVal(fullPathName)[i];
-            }
-            _wPathName[i] = 0;
+
+            _makeWchar(fullPathName, _wPathName, sizeof(_wPathName));
             do {
                 __threadErrno = 0;
                 // do not cast to INT - will loose sign bit then!
@@ -5076,7 +5075,7 @@
             } while ((ret < 0) && (__threadErrno == EINTR));
         }
 #else
-        ret = DeleteFileW((char *)__stringVal(fullPathName));
+        ret = DeleteFileW((wchar_t *)__unicode16StringVal(fullPathName));
         __threadErrno = __WIN32_ERR(GetLastError());
 #endif
         if (ret != TRUE) {
@@ -5100,7 +5099,6 @@
 
 %{
     int ret;
-    int eno;
 
     if (__isStringLike(oldPath) && __isStringLike(newPath)) {
 #ifdef DO_WRAP_CALLS
@@ -5112,26 +5110,53 @@
         do {
             __threadErrno = 0;
             // do not cast to INT - will loose sign bit then!
-            ret = STX_C_NOINT_CALL2( "rename", rename, _oldPath, _newPath);
-        } while ((ret < 0) && (__threadErrno == EINTR));
+            ret = STX_API_NOINT_CALL2("MoveFileA", MoveFileA, _oldPath, _newPath);
+        } while ((ret == 0) && (__threadErrno == EINTR));
 #else
         __BEGIN_INTERRUPTABLE__
         do {
             __threadErrno = 0;
-            ret = rename((char *) __stringVal(oldPath), (char *) __stringVal(newPath));
-        } while ((ret < 0) && (__threadErrno == EINTR));
+            ret = MoveFileA((char *) __stringVal(oldPath), (char *) __stringVal(newPath));
+        } while ((ret == 0) && (__threadErrno == EINTR));
         __END_INTERRUPTABLE__
 
-        if (ret < 0) {
+        if (ret == 0) {
             __threadErrno = __WIN32_ERR(GetLastError());
         }
 #endif
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
-    }
+    } else {
+        wchar_t _oldPathW[MAXPATHLEN], _newPathW[MAXPATHLEN];
+
+        if (_makeWchar(oldPath, _oldPathW, sizeof(_oldPathW)) < 0
+            || _makeWchar(newPath, _newPathW, sizeof(_newPathW)) < 0) {
+            goto err;
+        }
+#ifdef DO_WRAP_CALLS
+        do {
+            __threadErrno = 0;
+            // do not cast to INT - will loose sign bit then!
+            ret = STX_API_NOINT_CALL2( "MoveFileW", MoveFileW, _oldPathW, _newPathW);
+        } while ((ret == 0) && (__threadErrno == EINTR));
+#else
+        __BEGIN_INTERRUPTABLE__
+        do {
+            __threadErrno = 0;
+            ret = MoveFileW(_oldPathW, _newPathW);
+        } while ((ret == 0) && (__threadErrno == EINTR));
+        __END_INTERRUPTABLE__
+        if (ret == 0) {
+            __threadErrno = __WIN32_ERR(GetLastError());
+            RETURN(false);
+        }
+#endif
+    }
+    if (ret == 0) {
+        @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+        RETURN (false);
+    }
+    RETURN (true);
+
+err:;
 %}.
     ^ self primitiveFailed
 
@@ -5261,20 +5286,46 @@
         do {
             __threadErrno = 0;
             // do not cast to INT - will loose sign bit then!
-            ret = STX_C_NOINT_CALL2( "stat", stat, _aPathName, &buf);
+            ret = STX_C_NOINT_CALL2( "_stat", _stat, _aPathName, &buf);
         } while ((ret < 0) && (__threadErrno == EINTR));
 #else
         __BEGIN_INTERRUPTABLE__
         do {
             __threadErrno = 0;
-            ret = stat( (char *)__stringVal(aPathName), &buf);
+            ret = _stat( (char *)__stringVal(aPathName), &buf);
         } while ((ret < 0) && (__threadErrno == EINTR));
         __END_INTERRUPTABLE__
         if (ret < 0) {
             __threadErrno = __WIN32_ERR(GetLastError());
         }
 #endif
-
+        if (ret < 0) {
+            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+            RETURN ( nil );
+        }
+        RETURN ( __mkSmallInteger(buf.st_mode & 0777) );
+    } else if (__isUnicode16String(aPathName)) {
+#ifdef DO_WRAP_CALLS
+        char _wPathName[MAXPATHLEN];
+
+        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+
+        do {
+            __threadErrno = 0;
+            // do not cast to INT - will loose sign bit then!
+            ret = STX_C_NOINT_CALL2( "_wstat", _wstat, _wPathName, &buf);
+        } while ((ret < 0) && (__threadErrno == EINTR));
+#else
+        __BEGIN_INTERRUPTABLE__
+        do {
+            __threadErrno = 0;
+            ret = _wstat((char *)__unicode16StringVal(aPathName), &buf);
+        } while ((ret < 0) && (__threadErrno == EINTR));
+        __END_INTERRUPTABLE__
+        if (ret < 0) {
+            __threadErrno = __WIN32_ERR(GetLastError());
+        }
+#endif
         if (ret < 0) {
             @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
             RETURN ( nil );
@@ -5288,6 +5339,7 @@
     (OperatingSystem accessModeOf:'/') printStringRadix:8
     (OperatingSystem accessModeOf:'Make.proto') printStringRadix:8
     (OperatingSystem changeAccessModeOf:'Make.proto' to:8r644)
+    'Make.proto' asUnicode16String asFilename accessRights printStringRadix:8
    "
 !
 
@@ -5356,40 +5408,72 @@
 %{
     int ret;
 
-    if (__isStringLike(aPathName) && __isSmallInteger(modeBits)) {
+    if (__isSmallInteger(modeBits)) {
+        if (__isStringLike(aPathName)) {
 #ifdef DO_WRAP_CALLS
-        int chmod();
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = STX_C_NOINT_CALL2( "chmod", chmod, _aPathName, __intVal(modeBits));
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        __BEGIN_INTERRUPTABLE__
-        do {
-            __threadErrno = 0;
-            ret = chmod((char *)__stringVal(aPathName), __intVal(modeBits));
-        } while ((ret < 0) && (__threadErrno == EINTR));
-        __END_INTERRUPTABLE__
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN ( false );
-        }
-        RETURN ( true );
-    }
-%}.
-    ^ self primitiveFailed
+            int _chmod();
+            char _aPathName[MAXPATHLEN];
+
+            strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
+            do {
+                __threadErrno = 0;
+                // do not cast to INT - will loose sign bit then!
+                ret = STX_C_NOINT_CALL2( "_chmod", _chmod, _aPathName, __intVal(modeBits));
+            } while ((ret < 0) && (__threadErrno == EINTR));
+#else
+            __BEGIN_INTERRUPTABLE__
+            do {
+                __threadErrno = 0;
+                ret = _chmod((char *)__stringVal(aPathName), __intVal(modeBits));
+            } while ((ret < 0) && (__threadErrno == EINTR));
+            __END_INTERRUPTABLE__
+            if (ret < 0) {
+                __threadErrno = __WIN32_ERR(GetLastError());
+            }
+#endif
+            if (ret < 0) {
+                @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+                RETURN ( false );
+            }
+            RETURN ( true );
+
+        } else if (__isUnicode16String(aPathName)) {
+#ifdef DO_WRAP_CALLS
+            int _wchmod();
+            char _wPathName[MAXPATHLEN];
+
+            _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+            do {
+                __threadErrno = 0;
+                // do not cast to INT - will loose sign bit then!
+                ret = STX_C_NOINT_CALL2( "_wchmod", _wchmod, _wPathName, __intVal(modeBits));
+            } while ((ret < 0) && (__threadErrno == EINTR));
+#else
+            __BEGIN_INTERRUPTABLE__
+            do {
+                __threadErrno = 0;
+                ret = _chmod((wchar_t *)__unicode16StringVal(fullPathName), __intVal(modeBits));
+            } while ((ret < 0) && (__threadErrno == EINTR));
+            __END_INTERRUPTABLE__
+            if (ret < 0) {
+                __threadErrno = __WIN32_ERR(GetLastError());
+            }
+#endif
+            if (ret < 0) {
+                @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
+                RETURN ( false );
+            }
+            RETURN ( true );
+        }
+    }
+%}.
+    ^ self primitiveFailed:#argumentError
 
    "
     (OperatingSystem accessModeOf:'Make.proto') printStringRadix:8
     (OperatingSystem changeAccessModeOf:'Make.proto' to:8r644)
+    'Make.proto' asUnicode16String asFilename accessRights
+    'Make.proto' asUnicode16String asFilename accessRights:8r644
    "
 ! !
 
@@ -5719,19 +5803,17 @@
 
 %{
     int ret;
-
-    if (__isStringLike(aPathName)) {
+    wchar_t _aPathName[MAXPATHLEN];
+
+    if (_makeWchar(aPathName, _aPathName, sizeof(_aPathName)) > 0) {
 #ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
         do {
             __threadErrno = 0;
             // do not cast to INT - will loose sign bit then!
-            ret = (int)(STX_API_NOINT_CALL1( "GetDriveType", GetDriveType, _aPathName));
+            ret = (int)(STX_API_NOINT_CALL1( "GetDriveTypeW", GetDriveTypeW, _aPathName));
         } while ((ret < 0) && (__threadErrno == EINTR));
 #else
-        ret = GetDriveType((char *) __stringVal(aPathName));
+        ret = GetDriveTypeW(_aPathName);
         if (ret < 0) {
             __threadErrno = __WIN32_ERR(GetLastError());
         }
@@ -5793,44 +5875,21 @@
     int ret;
     wchar_t _aPathName[MAXPATHLEN+1];
 
-    if (__isStringLike(aPathName)) {
-        int i;
-        INT l = __stringSize(aPathName);
-
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __stringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
-    } else if (__isUnicode16String(aPathName)) {
-        int i;
-
-        INT l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
-    } else
-        goto badArgument;
-
+    if (_makeWchar(aPathName, _aPathName, sizeof(_aPathName)) > 0) {
 #ifdef DO_WRAP_CALLS
-     do {
-         __threadErrno = 0;
-         // do not cast to INT - will loose sign bit then!
-         ret = (int)(STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW, _aPathName, _aPathName, MAXPATHLEN));
-     } while ((ret == 0) && (__threadErrno == EINTR));
-#else
-     ret = GetLongPathNameW(_aPathName, _aPathName, MAXPATHLEN);
-     if (ret == 0) {
-         __threadErrno = __WIN32_ERR(GetLastError());
-     }
-#endif
-     RETURN (__mkStringOrU16String_maxlen(_aPathName, MAXPATHLEN));
-
-badArgument:;
+         do {
+             __threadErrno = 0;
+             // do not cast to INT - will loose sign bit then!
+             ret = (int)(STX_API_NOINT_CALL3( "GetLongPathNameW", GetLongPathNameW, _aPathName, _aPathName, MAXPATHLEN));
+         } while ((ret == 0) && (__threadErrno == EINTR));
+#else
+         ret = GetLongPathNameW(_aPathName, _aPathName, MAXPATHLEN);
+         if (ret == 0) {
+             __threadErrno = __WIN32_ERR(GetLastError());
+         }
+#endif
+         RETURN (__mkStringOrU16String_maxlen(_aPathName, MAXPATHLEN));
+    }
 %}.
     ^ self primitiveFailed
 
@@ -5870,42 +5929,21 @@
     int ret;
     wchar_t _aPathName[MAXPATHLEN+1];
 
-    if (__isStringLike(aPathName)) {
-        int i;
-        int l = __stringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __stringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
-    } else if (__isUnicode16String(aPathName)) {
-        int i;
-        int l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
-    } else
-        goto badArgument;
-
+    if (_makeWchar(aPathName, _aPathName, sizeof(_aPathName)) > 0) {
 #ifdef DO_WRAP_CALLS
-     do {
-         __threadErrno = 0;
-         // do not cast to INT - will loose sign bit then!
-         ret = (int)(STX_API_NOINT_CALL3( "GetShortPathNameW", GetShortPathNameW, _aPathName, _aPathName, MAXPATHLEN));
-     } while ((ret == 0) && (__threadErrno == EINTR));
-#else
-     ret = GetShortPathNameW(_aPathName, _aPathName, MAXPATHLEN);
-     if (ret == 0) {
-         __threadErrno = __WIN32_ERR(GetLastError());
+         do {
+             __threadErrno = 0;
+             // do not cast to INT - will loose sign bit then!
+             ret = (int)(STX_API_NOINT_CALL3( "GetShortPathNameW", GetShortPathNameW, _aPathName, _aPathName, MAXPATHLEN));
+         } while ((ret == 0) && (__threadErrno == EINTR));
+#else
+         ret = GetShortPathNameW(_aPathName, _aPathName, MAXPATHLEN);
+         if (ret == 0) {
+             __threadErrno = __WIN32_ERR(GetLastError());
+         }
+#endif
+         RETURN (__mkStringOrU16String_maxlen(_aPathName, MAXPATHLEN));
      }
-#endif
-     RETURN ( __MKU16STRING(_aPathName));
-
-badArgument:;
 %}.
     ^ self primitiveFailed
 
@@ -6000,14 +6038,8 @@
 #endif
     } else if (__isUnicode16String(aPathName)) {
         wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
+
+        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
 #ifdef DO_WRAP_CALLS
         do {
             __threadErrno = 0;
@@ -6075,75 +6107,14 @@
     "return true, if the file/dir 'aPathName' is readable.
      For symbolic links, the pointed-to-file is checked."
 
-%{
-    if (__isStringLike(aPathName)) {
-        int ret;
-
-        /*
-         * under windows, all files are readable ...
-         * so, only check for the files existence here.
-         */
-#ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName));
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesA((char *) __stringVal(aPathName));
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
-    }
-
-    if (__isUnicode16String(aPathName)) {
-        int ret;
-
-        /*
-         * under windows, all files are readable ...
-         * so, only check for the files existence here.
-         */
-        wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
-#ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName));
-        } while ((ret < 0) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesW(_wPathName);
-        if (ret < 0) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-        if (ret < 0) {
-            @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-            RETURN (false);
-        }
-        RETURN (true);
-    }
-%}.
-    ^ self primitiveFailed
+    "under windows, all files are readable ...
+     so, only check for the files existence here"
+
+    ^ (self primGetFileAttributes:aPathName) notNil.
 
     "
      self isReadable:'.'
+     self isReadable:'ughoiweuhiourw'
      self isReadable:'.' asUnicode16String
     "
 !
@@ -6167,67 +6138,7 @@
     "return true, if 'aPathName' is a valid path name
      (i.e. the file or directory exists)"
 
-%{
-    int ret;
-
-    if (__isStringLike(aPathName)) {
-#ifdef DO_WRAP_CALLS
-        char _aPathName[MAXPATHLEN];
-
-        strncpy(_aPathName, __stringVal(aPathName), MAXPATHLEN-1); _aPathName[MAXPATHLEN-1] = '\0';
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(STX_API_NOINT_CALL1( "GetFileAttributesA", GetFileAttributesA, _aPathName));
-        } while ((ret == -1) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesA((char *) __stringVal(aPathName));
-        if (ret == -1) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-    } else  if (__isUnicode16String(aPathName)) {
-        wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
-#ifdef DO_WRAP_CALLS
-        do {
-            __threadErrno = 0;
-            // do not cast to INT - will loose sign bit then!
-            ret = (int)(STX_API_NOINT_CALL1( "GetFileAttributesW", GetFileAttributesW, _wPathName));
-        } while ((ret == -1) && (__threadErrno == EINTR));
-#else
-        ret = GetFileAttributesW(_wPathName);
-        if (ret == -1) {
-            __threadErrno = __WIN32_ERR(GetLastError());
-        }
-#endif
-    } else
-        goto err;
-
-    if (ret == -1) {
-        @global(LastErrorNumber) = __mkSmallInteger(__threadErrno);
-        RETURN ( false );
-    }
-    RETURN (true);
-
-err:;
-%}.
-    aPathName isString ifTrue:[
-        aPathName isUnicode32String ifTrue:[
-            "/ WIN32 only support 16 bit (wide) strings
-            ^ self isValidPath:aPathName asUnicode16String
-        ]
-    ].
-    ^ self primitiveFailed
-
-    "Modified: / 05-07-2006 / 17:23:51 / cg"
+    ^ (self primGetFileAttributes:aPathName) notNil.
 !
 
 isWritable:aPathName
@@ -6291,27 +6202,9 @@
     int modeBits = 0;
     WIN32_FILE_ATTRIBUTE_DATA fileAttributeData;
     unsigned INT ino;
-    wchar_t _aPathName[MAXPATHLEN+1];
-
-    if (__isStringLike(aPathName)) {
-        int i;
-        int l = __stringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __stringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
-    } else if (__isUnicode16String(aPathName)) {
-        int i;
-        int l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
-    } else
+    wchar_t _wPathName[MAXPATHLEN+1];
+
+    if (_makeWchar(aPathName, _wPathName, sizeof(_wPathName)) < 0)
         goto badArgument;
 
 #ifdef DO_WRAP_CALLS
@@ -6319,11 +6212,11 @@
         do {
             __threadErrno = 0;
             // do not cast to INT - will loose sign bit then!
-            result = (int)(STX_API_NOINT_CALL3( "GetFileAttributesExW", GetFileAttributesExW, _aPathName, GetFileExInfoStandard, &fileAttributeData));
+            result = (int)(STX_API_NOINT_CALL3( "GetFileAttributesExW", GetFileAttributesExW, _wPathName, GetFileExInfoStandard, &fileAttributeData));
         } while (!result && (__threadErrno == EINTR));
     }
 #else
-    result = GetFileAttributesExW(_aPathName, GetFileExInfoStandard, &fileAttributeData);
+    result = GetFileAttributesExW(_wPathName, GetFileExInfoStandard, &fileAttributeData);
     if (!result) {
         __threadErrno = __WIN32_ERR(GetLastError());
     }
@@ -6539,14 +6432,9 @@
 
     if (__isUnicode16String(aPathName)) {
         wchar_t _wPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _wPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _wPathName[i] = 0;
+
+        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
+
 #ifdef DO_WRAP_CALLS
         do {
             __threadErrno = 0;
@@ -6566,6 +6454,11 @@
         RETURN (nil);
     }
 %}.
+    (aPathName isString and:[aPathName isUnicode32String]) ifTrue:[
+        "/ WIN32 only support 16 bit (wide) strings
+        ^ self primGetFileAttributes:aPathName asUnicode16String
+    ].
+
     ^ self primitiveFailed
 
     "
@@ -6573,6 +6466,7 @@
      self primGetFileAttributes:'bc.mak'
 
      self primGetFileAttributes:'.' asUnicodeString
+     self primGetFileAttributes:'.' asUnicode32String
      self primGetFileAttributes:'bc.mak' asUnicodeString
     "
 !
@@ -6636,23 +6530,17 @@
         wchar_t nameBuffer2[MAXPATHLEN + 1];
         wchar_t *returnedName = NULL;
         int rslt;
-        wchar_t _aPathName[MAXPATHLEN+1];
-        int i, l;
-
-        l = __unicode16StringSize(aPathName);
-        if (l > MAXPATHLEN) l = MAXPATHLEN;
-        for (i=0; i<l; i++) {
-            _aPathName[i] = __unicode16StringVal(aPathName)[i];
-        }
-        _aPathName[i] = 0;
+        wchar_t _wPathName[MAXPATHLEN+1];
+
+        _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
 
 #ifdef DO_WRAP_CALLS
         do {
             __threadErrno = 0;
-            rslt = (int)(STX_API_NOINT_CALL4( "GetFullPathNameW", GetFullPathNameW, _aPathName, MAXPATHLEN, nameBuffer, NULL));
+            rslt = (int)(STX_API_NOINT_CALL4( "GetFullPathNameW", GetFullPathNameW, _wPathName, MAXPATHLEN, nameBuffer, NULL));
         } while ((rslt < 0) && (__threadErrno == EINTR));
 #else
-        rslt = GetFullPathNameW(_aPathName, MAXPATHLEN, nameBuffer, NULL);
+        rslt = GetFullPathNameW(_wPathName, MAXPATHLEN, nameBuffer, NULL);
 #endif
 
         returnedName = nameBuffer;
@@ -6670,7 +6558,7 @@
             returnedName = nameBuffer2;
         }
         if (rslt > 0) {
-            RETURN ( __MKU16STRING(returnedName) );
+            RETURN (__mkStringOrU16String_maxlen(returnedName, MAXPATHLEN));
         }
         __threadErrno = __WIN32_ERR(GetLastError());
         RETURN (nil);
@@ -6742,14 +6630,8 @@
 
         if (__isUnicode16String(aPathName)) {
             wchar_t _wPathName[MAXPATHLEN+1];
-            int i, l;
-
-            l = __unicode16StringSize(aPathName);
-            if (l > MAXPATHLEN) l = MAXPATHLEN;
-            for (i=0; i<l; i++) {
-                _wPathName[i] = __unicode16StringVal(aPathName)[i];
-            }
-            _wPathName[i] = 0;
+
+            _makeWchar(aPathName, _wPathName, sizeof(_wPathName));
 #ifdef DO_WRAP_CALLS
             do {
                 __threadErrno = 0;
@@ -9398,10 +9280,10 @@
      On non-windows systems, nil is returned."
 
 %{
-    char buffer[MAXPATHLEN+1];
-
-    if (GetWindowsDirectory(buffer, MAXPATHLEN)) {
-        RETURN (__MKSTRING(buffer));
+    wchar_t buffer[MAXPATHLEN+1];
+
+    if (GetWindowsDirectoryW(buffer, MAXPATHLEN)) {
+        RETURN (__mkStringOrU16String_maxlen(buffer, MAXPATHLEN));
     }
 %}.
     ^ nil
@@ -9419,10 +9301,10 @@
      On non-windows systems, nil is returned."
 
 %{
-    char buffer[MAXPATHLEN+1];
-
-    if (GetSystemDirectory(buffer, MAXPATHLEN)) {
-        RETURN (__MKSTRING(buffer));
+    wchar_t buffer[MAXPATHLEN+1];
+
+    if (GetSystemDirectoryW(buffer, MAXPATHLEN)) {
+        RETURN (__mkStringOrU16String_maxlen(buffer, MAXPATHLEN));
     }
 %}.
     ^ nil
@@ -11272,7 +11154,7 @@
     bias = __mkSmallInteger(tzInfo.Bias);
     memmove(nm, tzInfo.StandardName, 32*sizeof(WCHAR));
     nm[32] = 0;
-    standardName = __MKU16STRING(nm);
+    standardName = __mkStringOrU16String_maxlen(nm, sizeof(nm));
     standardDate_y = __mkSmallInteger(tzInfo.StandardDate.wYear);
     standardDate_m = __mkSmallInteger(tzInfo.StandardDate.wMonth);
     standardDate_d = __mkSmallInteger(tzInfo.StandardDate.wDay);
@@ -11283,7 +11165,7 @@
     standardBias =  __mkSmallInteger(tzInfo.StandardBias);
     memmove(nm, tzInfo.DaylightName, 32*sizeof(WCHAR));
     nm[32] = 0;
-    daylightName = __MKU16STRING(nm);
+    daylightName = __mkStringOrU16String_maxlen(nm, sizeof(nm));
     daylightDate_y = __mkSmallInteger(tzInfo.DaylightDate.wYear);
     daylightDate_m = __mkSmallInteger(tzInfo.DaylightDate.wMonth);
     daylightDate_d = __mkSmallInteger(tzInfo.DaylightDate.wDay);
--- a/WriteStream.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/WriteStream.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1989 by Claus Gittinger
 	      All Rights Reserved
@@ -285,7 +287,7 @@
 !
 
 isReadable
-    "return true if the receiver supports reading - thats not true"
+    "return true if the receiver supports reading - that's not true"
 
     ^ false
 
--- a/ZeroDivide.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/ZeroDivide.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2001 by eXept Software AG
               All Rights Reserved
@@ -11,6 +13,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 DomainError subclass:#ZeroDivide
 	instanceVariableNames:''
 	classVariableNames:''
@@ -76,7 +80,7 @@
 !ZeroDivide methodsFor:'accessing'!
 
 defaultResumeValue
-    "no, we return infinity here, if ever proceeded"
+    "return infinity here, if ever proceeded"
 
     ^ parameter receiver class infinity
 
@@ -129,7 +133,7 @@
 !ZeroDivide class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ZeroDivide.st,v 1.8 2013-01-25 17:19:34 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
--- a/abbrev.stc	Tue Sep 20 11:37:33 2016 +0100
+++ b/abbrev.stc	Mon Oct 03 12:44:41 2016 +0100
@@ -181,9 +181,7 @@
 CharacterEncoderImplementations::ISO8859_9 CharacterEncoderImplementations__ISO8859_9 stx:libbasic 'Collections-Text-Encodings' 0
 CharacterEncoderImplementations::KOI8_U CharacterEncoderImplementations__KOI8_U stx:libbasic 'Collections-Text-Encodings' 0
 CheapBlock CheapBlock stx:libbasic 'Kernel-Methods' 0
-ClassBuildError ClassBuildError stx:libbasic 'Kernel-Support' 1
 CmdLineOptionError CmdLineOptionError stx:libbasic 'System-Support-Command line' 1
-ElementBoundsError ElementBoundsError stx:libbasic 'Kernel-Exceptions-Errors' 1
 Fraction Fraction stx:libbasic 'Magnitude-Numbers' 0
 GetOpt GetOpt stx:libbasic 'System-Support' 0
 IdentityDictionary IdentityDictionary stx:libbasic 'Collections-Unordered' 0
@@ -232,9 +230,6 @@
 AbortOperationRequest AbortOperationRequest stx:libbasic 'Kernel-Exceptions-Control' 1
 AbstractNumberVector AbstractNumberVector stx:libbasic 'Collections-Arrayed' 0
 AllocationFailure AllocationFailure stx:libbasic 'System-Support' 1
-AmbiguousMessage AmbiguousMessage stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
-ArithmeticError ArithmeticError stx:libbasic 'Kernel-Exceptions-Errors' 1
-AssertionFailedError AssertionFailedError stx:libbasic 'Kernel-Exceptions-Errors' 1
 AutoloadMetaclass AutoloadMetaclass stx:libbasic 'Kernel-Classes' 0
 ByteArray ByteArray stx:libbasic 'Collections-Arrayed' 0
 CharacterArray CharacterArray stx:libbasic 'Collections-Text' 0
@@ -242,7 +237,6 @@
 Class Class stx:libbasic 'Kernel-Classes' 0
 ClassBuildWarning ClassBuildWarning stx:libbasic 'Kernel-Support' 1
 ClassLoadInProgressQuery ClassLoadInProgressQuery stx:libbasic 'Kernel-Exceptions-Queries' 1
-ContextError ContextError stx:libbasic 'Kernel-Exceptions-Errors' 1
 ConversionError ConversionError stx:libbasic 'Kernel-Exceptions-Errors' 1
 DeepCopyError DeepCopyError stx:libbasic 'Kernel-Exceptions-Errors' 1
 ExceptionHandlerSet ExceptionHandlerSet stx:libbasic 'Kernel-Exceptions' 0
@@ -255,9 +249,6 @@
 InvalidPatchError InvalidPatchError stx:libbasic 'Kernel-Exceptions-Errors' 1
 LargeInteger LargeInteger stx:libbasic 'Magnitude-Numbers' 0
 LongFloat LongFloat stx:libbasic 'Magnitude-Numbers' 0
-MessageNotUnderstood MessageNotUnderstood stx:libbasic 'Kernel-Exceptions-Errors' 1
-NoModificationError NoModificationError stx:libbasic 'Kernel-Exceptions-Errors' 1
-NotFoundError NotFoundError stx:libbasic 'Kernel-Exceptions-Errors' 1
 OSSignalInterrupt OSSignalInterrupt stx:libbasic 'Kernel-Exceptions-Control' 1
 OSXOperatingSystem OSXOperatingSystem stx:libbasic 'OS-Unix' 0
 OsIllegalOperation OsIllegalOperation stx:libbasic 'OS-Support' 1
@@ -273,104 +264,113 @@
 ProceedError ProceedError stx:libbasic 'Kernel-Exceptions-Errors' 1
 ReadWriteStream ReadWriteStream stx:libbasic 'Streams' 0
 ShortFloat ShortFloat stx:libbasic 'Magnitude-Numbers' 0
-SignalError SignalError stx:libbasic 'Kernel-Exceptions-Errors' 1
 SmallInteger SmallInteger stx:libbasic 'Magnitude-Numbers' 0
 SmalltalkChunkFileSourceWriter SmalltalkChunkFileSourceWriter stx:libbasic 'Kernel-Classes-Support' 0
 SomeNumber SomeNumber stx:libbasic 'Magnitude-Numbers' 0
 StreamError StreamError stx:libbasic 'Kernel-Exceptions-Errors' 1
-SubclassResponsibilityError SubclassResponsibilityError stx:libbasic 'Kernel-Exceptions-Errors' 1
 TimeoutError TimeoutError stx:libbasic 'Kernel-Exceptions-Errors' 1
-UnimplementedFunctionalityError UnimplementedFunctionalityError stx:libbasic 'Kernel-Exceptions-Errors' 1
 UserPreferences UserPreferences stx:libbasic 'System-Support' 0
 VarArgCheapBlock VarArgCheapBlock stx:libbasic 'Kernel-Methods' 0
 WeakIdentityDictionary WeakIdentityDictionary stx:libbasic 'Collections-Weak' 0
 WeakValueIdentityDictionary WeakValueIdentityDictionary stx:libbasic 'Collections-Weak' 0
+AmbiguousMessage AmbiguousMessage stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
 ArgumentError ArgumentError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
-CannotResumeError CannotResumeError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
-CannotReturnError CannotReturnError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
+ArithmeticError ArithmeticError stx:libbasic 'Kernel-Exceptions-Errors' 1
+AssertionFailedError AssertionFailedError stx:libbasic 'Kernel-Exceptions-Errors' 1
 CharacterEncoderError CharacterEncoderError stx:libbasic 'Collections-Text-Encodings' 1
+ClassBuildError ClassBuildError stx:libbasic 'Kernel-Support' 1
+ContextError ContextError stx:libbasic 'Kernel-Exceptions-Errors' 1
 DateConversionError DateConversionError stx:libbasic 'Magnitude-Time' 1
-DomainError DomainError stx:libbasic 'Kernel-Exceptions-Errors' 1
 DoubleArray DoubleArray stx:libbasic 'Collections-Arrayed' 0
+ElementBoundsError ElementBoundsError stx:libbasic 'Kernel-Exceptions-Errors' 1
 EndOfStreamError EndOfStreamError stx:libbasic 'Kernel-Exceptions-Errors' 1
 ExternalStream ExternalStream stx:libbasic 'Streams-External' 0
 ExternalStructure ExternalStructure stx:libbasic 'System-Support' 1
 FloatArray FloatArray stx:libbasic 'Collections-Arrayed' 0
 ImmutableByteArray ImmutableByteArray stx:libbasic 'System-Compiler-Support' 0
 IncompleteNextCountError IncompleteNextCountError stx:libbasic 'Kernel-Exceptions-Errors' 1
-IndexNotFoundError IndexNotFoundError stx:libbasic 'Kernel-Exceptions-Errors' 1
 InvalidCodeError InvalidCodeError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
 InvalidModeError InvalidModeError stx:libbasic 'Kernel-Exceptions-Errors' 1
 InvalidOperationError InvalidOperationError stx:libbasic 'Kernel-Exceptions-Errors' 1
 InvalidTypeError InvalidTypeError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
-KeyNotFoundError KeyNotFoundError stx:libbasic 'Kernel-Exceptions-Errors' 1
 MallocFailure MallocFailure stx:libbasic 'System-Support' 1
+MessageNotUnderstood MessageNotUnderstood stx:libbasic 'Kernel-Exceptions-Errors' 1
 MethodNotAppropriateError MethodNotAppropriateError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
-MissingClassInLiteralArrayErrorSignal MissingClassInLiteralArrayErrorSignal stx:libbasic 'Kernel-Exceptions-Errors' 1
+NoModificationError NoModificationError stx:libbasic 'Kernel-Exceptions-Errors' 1
 NonBooleanReceiverError NonBooleanReceiverError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
+NotFoundError NotFoundError stx:libbasic 'Kernel-Exceptions-Errors' 1
 NumberConversionError NumberConversionError stx:libbasic 'Magnitude-Numbers' 1
 OpenError OpenError stx:libbasic 'Kernel-Exceptions-Errors' 1
 PackageNotFoundError PackageNotFoundError stx:libbasic 'Kernel-Exceptions-Errors' 1
 PositionError PositionError stx:libbasic 'Kernel-Exceptions-Errors' 1
 PositionOutOfBoundsError PositionOutOfBoundsError stx:libbasic 'Kernel-Exceptions-Errors' 1
 PrimitiveFailure PrimitiveFailure stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
-RangeError RangeError stx:libbasic 'Kernel-Exceptions-Errors' 1
 ReadError ReadError stx:libbasic 'Kernel-Exceptions-Errors' 1
 Registry Registry stx:libbasic 'Collections-Weak' 0
+SignalError SignalError stx:libbasic 'Kernel-Exceptions-Errors' 1
 SignedByteArray SignedByteArray stx:libbasic 'Collections-Arrayed' 0
 StreamIOError StreamIOError stx:libbasic 'Kernel-Exceptions-Errors' 1
 StreamNotOpenError StreamNotOpenError stx:libbasic 'Kernel-Exceptions-Errors' 1
 String String stx:libbasic 'Collections-Text' 0
+SubclassResponsibilityError SubclassResponsibilityError stx:libbasic 'Kernel-Exceptions-Errors' 1
 TimeConversionError TimeConversionError stx:libbasic 'Magnitude-Time' 1
 TwoByteString TwoByteString stx:libbasic 'Collections-Text' 0
-UnorderedNumbersError UnorderedNumbersError stx:libbasic 'Kernel-Exceptions-Errors' 1
+UnimplementedFunctionalityError UnimplementedFunctionalityError stx:libbasic 'Kernel-Exceptions-Errors' 1
 UnprotectedExternalBytes UnprotectedExternalBytes stx:libbasic 'System-Support' 0
 WeakDependencyDictionary WeakDependencyDictionary stx:libbasic 'Collections-Weak' 0
 WriteError WriteError stx:libbasic 'Kernel-Exceptions-Errors' 1
-WrongProceedabilityError WrongProceedabilityError stx:libbasic 'Kernel-Exceptions-Errors' 1
 AbstractClassInstantiationError AbstractClassInstantiationError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
 BadLiteralsError BadLiteralsError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
 CachingRegistry CachingRegistry stx:libbasic 'System-Support' 0
+CannotResumeError CannotResumeError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
+CannotReturnError CannotReturnError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
 DecodingError DecodingError stx:libbasic 'Collections-Text-Encodings' 1
+DomainError DomainError stx:libbasic 'Kernel-Exceptions-Errors' 1
 EncodingError EncodingError stx:libbasic 'Collections-Text-Encodings' 1
 FileDoesNotExistException FileDoesNotExistException stx:libbasic 'Kernel-Exceptions-Errors' 1
 FileStream FileStream stx:libbasic 'Streams-External' 0
 HandleRegistry HandleRegistry stx:libbasic 'System-Support' 0
 ImmutableString ImmutableString stx:libbasic 'System-Compiler-Support' 0
+IndexNotFoundError IndexNotFoundError stx:libbasic 'Kernel-Exceptions-Errors' 1
 InvalidByteCodeError InvalidByteCodeError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
 InvalidInstructionError InvalidInstructionError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
 InvalidReadError InvalidReadError stx:libbasic 'Kernel-Exceptions-Errors' 1
 InvalidWriteError InvalidWriteError stx:libbasic 'Kernel-Exceptions-Errors' 1
+KeyNotFoundError KeyNotFoundError stx:libbasic 'Kernel-Exceptions-Errors' 1
+MissingClassInLiteralArrayErrorSignal MissingClassInLiteralArrayErrorSignal stx:libbasic 'Kernel-Exceptions-Errors' 1
 NoByteCodeError NoByteCodeError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
-NonIntegerIndexError NonIntegerIndexError stx:libbasic 'Kernel-Exceptions-Errors' 1
 NonPositionableExternalStream NonPositionableExternalStream stx:libbasic 'Streams-External' 0
 NumberFormatError NumberFormatError stx:libbasic 'Magnitude-Numbers' 1
-OverflowError OverflowError stx:libbasic 'Kernel-Exceptions-Errors' 1
 PTYOpenError PTYOpenError stx:libbasic 'Kernel-Exceptions-Errors' 1
 PackageNotCompatibleError PackageNotCompatibleError stx:libbasic 'Kernel-Exceptions-Errors' 1
-SubscriptOutOfBoundsError SubscriptOutOfBoundsError stx:libbasic 'Kernel-Exceptions-Errors' 1
+RangeError RangeError stx:libbasic 'Kernel-Exceptions-Errors' 1
 Symbol Symbol stx:libbasic 'Collections-Text' 0
-UnderflowError UnderflowError stx:libbasic 'Kernel-Exceptions-Errors' 1
 Unicode16String Unicode16String stx:libbasic 'Collections-Text' 0
+UnorderedNumbersError UnorderedNumbersError stx:libbasic 'Kernel-Exceptions-Errors' 1
 WrongNumberOfArgumentsError WrongNumberOfArgumentsError stx:libbasic 'Kernel-Exceptions-ExecutionErrors' 1
-ZeroDivide ZeroDivide stx:libbasic 'Kernel-Exceptions-Errors' 1
+WrongProceedabilityError WrongProceedabilityError stx:libbasic 'Kernel-Exceptions-Errors' 1
 CharacterRangeError CharacterRangeError stx:libbasic 'Collections-Text-Encodings' 1
 DirectoryStream DirectoryStream stx:libbasic 'Streams-External' 0
 InvalidEncodingError InvalidEncodingError stx:libbasic 'Collections-Text-Encodings' 1
+NonIntegerIndexError NonIntegerIndexError stx:libbasic 'Kernel-Exceptions-Errors' 1
+OverflowError OverflowError stx:libbasic 'Kernel-Exceptions-Errors' 1
 PipeStream PipeStream stx:libbasic 'Streams-External' 0
 RomanNumberFormatError RomanNumberFormatError stx:libbasic 'Magnitude-Numbers' 1
-SqueakCommentReader SqueakCommentReader stx:libbasic 'Kernel-Support' 0
+SubscriptOutOfBoundsError SubscriptOutOfBoundsError stx:libbasic 'Kernel-Exceptions-Errors' 1
+UnderflowError UnderflowError stx:libbasic 'Kernel-Exceptions-Errors' 1
+ZeroDivide ZeroDivide stx:libbasic 'Kernel-Exceptions-Errors' 1
 Win32Process Win32Process stx:libbasic  'unknownCategory'  0
 PCFilename PCFilename stx:libbasic  'unknownCategory'  0
 Win32Constants Win32Constants stx:libbasic  'unknownCategory'  0
 Win32Handle Win32Handle stx:libbasic  'unknownCategory'  0
-SimpleExternalLibraryFunction SimpleExternalLibraryFunction stx:libbasic 'System-Support' 0
 Win32FILEHandle Win32FILEHandle stx:libbasic  'unknownCategory'  0
 Win32OperatingSystem Win32OperatingSystem stx:libbasic  'unknownCategory'  0
-QualifiedName QualifiedName stx:libbasic 'Kernel-Support' 0
 OpenVMSFileHandle OpenVMSFileHandle stx:libbasic  'unknownCategory'  0
 OpenVMSFilename OpenVMSFilename stx:libbasic  'unknownCategory'  0
 OpenVMSOperatingSystem OpenVMSOperatingSystem stx:libbasic  'unknownCategory'  0
+SqueakCommentReader SqueakCommentReader stx:libbasic 'Kernel-Support' 0
+SimpleExternalLibraryFunction SimpleExternalLibraryFunction stx:libbasic 'System-Support' 0
+QualifiedName QualifiedName stx:libbasic 'Kernel-Support' 0
 AbstractDesktop AbstractDesktop stx:libbasic 'System-Desktop' 0
 BadRomanNumberFormatError BadRomanNumberFormatError stx:libbasic 'Magnitude-Numbers' 1
 CharacterEncoderImplementations::BIG5 CharacterEncoderImplementations__BIG5 stx:libbasic 'Collections-Text-Encodings' 0
--- a/bc.mak	Tue Sep 20 11:37:33 2016 +0100
+++ b/bc.mak	Mon Oct 03 12:44:41 2016 +0100
@@ -250,9 +250,7 @@
 $(OUTDIR)CharacterEncoderImplementations__ISO8859_9.$(O) CharacterEncoderImplementations__ISO8859_9.$(C) CharacterEncoderImplementations__ISO8859_9.$(H): CharacterEncoderImplementations__ISO8859_9.st $(INCLUDE_TOP)\stx\libbasic\CharacterEncoder.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterEncoderImplementations__ISO8859_1.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterEncoderImplementations__SingleByteEncoder.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)CharacterEncoderImplementations__KOI8_U.$(O) CharacterEncoderImplementations__KOI8_U.$(C) CharacterEncoderImplementations__KOI8_U.$(H): CharacterEncoderImplementations__KOI8_U.st $(INCLUDE_TOP)\stx\libbasic\CharacterEncoder.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterEncoderImplementations__KOI8_R.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterEncoderImplementations__SingleByteEncoder.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)CheapBlock.$(O) CheapBlock.$(C) CheapBlock.$(H): CheapBlock.st $(INCLUDE_TOP)\stx\libbasic\Block.$(H) $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ClassBuildError.$(O) ClassBuildError.$(C) ClassBuildError.$(H): ClassBuildError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)CmdLineOptionError.$(O) CmdLineOptionError.$(C) CmdLineOptionError.$(H): CmdLineOptionError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)ElementBoundsError.$(O) ElementBoundsError.$(C) ElementBoundsError.$(H): ElementBoundsError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Fraction.$(O) Fraction.$(C) Fraction.$(H): Fraction.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticValue.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Number.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)GetOpt.$(O) GetOpt.$(C) GetOpt.$(H): GetOpt.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
 $(OUTDIR)IdentityDictionary.$(O) IdentityDictionary.$(C) IdentityDictionary.$(H): IdentityDictionary.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
@@ -298,9 +296,6 @@
 $(OUTDIR)AbortOperationRequest.$(O) AbortOperationRequest.$(C) AbortOperationRequest.$(H): AbortOperationRequest.st $(INCLUDE_TOP)\stx\libbasic\AbortAllOperationRequest.$(H) $(INCLUDE_TOP)\stx\libbasic\ControlRequest.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)AbstractNumberVector.$(O) AbstractNumberVector.$(C) AbstractNumberVector.$(H): AbstractNumberVector.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)AllocationFailure.$(O) AllocationFailure.$(C) AllocationFailure.$(H): AllocationFailure.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)AmbiguousMessage.$(O) AmbiguousMessage.$(C) AmbiguousMessage.$(H): AmbiguousMessage.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)ArithmeticError.$(O) ArithmeticError.$(C) ArithmeticError.$(H): ArithmeticError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)AssertionFailedError.$(O) AssertionFailedError.$(C) AssertionFailedError.$(H): AssertionFailedError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)AutoloadMetaclass.$(O) AutoloadMetaclass.$(C) AutoloadMetaclass.$(H): AutoloadMetaclass.st $(INCLUDE_TOP)\stx\libbasic\Behavior.$(H) $(INCLUDE_TOP)\stx\libbasic\ClassDescription.$(H) $(INCLUDE_TOP)\stx\libbasic\Metaclass.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ByteArray.$(O) ByteArray.$(C) ByteArray.$(H): ByteArray.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)CharacterArray.$(O) CharacterArray.$(C) CharacterArray.$(H): CharacterArray.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
@@ -308,7 +303,6 @@
 $(OUTDIR)Class.$(O) Class.$(C) Class.$(H): Class.st $(INCLUDE_TOP)\stx\libbasic\Array.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Association.$(H) $(INCLUDE_TOP)\stx\libbasic\Behavior.$(H) $(INCLUDE_TOP)\stx\libbasic\ClassDescription.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\LookupKey.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(STCHDR)
 $(OUTDIR)ClassBuildWarning.$(O) ClassBuildWarning.$(C) ClassBuildWarning.$(H): ClassBuildWarning.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\UserNotification.$(H) $(INCLUDE_TOP)\stx\libbasic\Warning.$(H) $(STCHDR)
 $(OUTDIR)ClassLoadInProgressQuery.$(O) ClassLoadInProgressQuery.$(C) ClassLoadInProgressQuery.$(H): ClassLoadInProgressQuery.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\LoadInProgressQuery.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Query.$(H) $(STCHDR)
-$(OUTDIR)ContextError.$(O) ContextError.$(C) ContextError.$(H): ContextError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)ConversionError.$(O) ConversionError.$(C) ConversionError.$(H): ConversionError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DeepCopyError.$(O) DeepCopyError.$(C) DeepCopyError.$(H): DeepCopyError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)ExceptionHandlerSet.$(O) ExceptionHandlerSet.$(C) ExceptionHandlerSet.$(H): ExceptionHandlerSet.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
@@ -321,9 +315,6 @@
 $(OUTDIR)InvalidPatchError.$(O) InvalidPatchError.$(C) InvalidPatchError.$(H): InvalidPatchError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)LargeInteger.$(O) LargeInteger.$(C) LargeInteger.$(H): LargeInteger.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticValue.$(H) $(INCLUDE_TOP)\stx\libbasic\Integer.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Number.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)LongFloat.$(O) LongFloat.$(C) LongFloat.$(H): LongFloat.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticValue.$(H) $(INCLUDE_TOP)\stx\libbasic\LimitedPrecisionReal.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Number.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)MessageNotUnderstood.$(O) MessageNotUnderstood.$(C) MessageNotUnderstood.$(H): MessageNotUnderstood.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)NoModificationError.$(O) NoModificationError.$(C) NoModificationError.$(H): NoModificationError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)NotFoundError.$(O) NotFoundError.$(C) NotFoundError.$(H): NotFoundError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)OSSignalInterrupt.$(O) OSSignalInterrupt.$(C) OSSignalInterrupt.$(H): OSSignalInterrupt.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)OsIllegalOperation.$(O) OsIllegalOperation.$(C) OsIllegalOperation.$(H): OsIllegalOperation.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OsError.$(H) $(STCHDR)
 $(OUTDIR)OsInaccessibleError.$(O) OsInaccessibleError.$(C) OsInaccessibleError.$(H): OsInaccessibleError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OsError.$(H) $(STCHDR)
@@ -338,92 +329,101 @@
 $(OUTDIR)ProceedError.$(O) ProceedError.$(C) ProceedError.$(H): ProceedError.st $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Notification.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\UserNotification.$(H) $(INCLUDE_TOP)\stx\libbasic\Warning.$(H) $(STCHDR)
 $(OUTDIR)ReadWriteStream.$(O) ReadWriteStream.$(C) ReadWriteStream.$(H): ReadWriteStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
 $(OUTDIR)ShortFloat.$(O) ShortFloat.$(C) ShortFloat.$(H): ShortFloat.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticValue.$(H) $(INCLUDE_TOP)\stx\libbasic\LimitedPrecisionReal.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Number.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
-$(OUTDIR)SignalError.$(O) SignalError.$(C) SignalError.$(H): SignalError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)SmallInteger.$(O) SmallInteger.$(C) SmallInteger.$(H): SmallInteger.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticValue.$(H) $(INCLUDE_TOP)\stx\libbasic\Integer.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\Number.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SmalltalkChunkFileSourceWriter.$(O) SmalltalkChunkFileSourceWriter.$(C) SmalltalkChunkFileSourceWriter.$(H): SmalltalkChunkFileSourceWriter.st $(INCLUDE_TOP)\stx\libbasic\AbstractSourceFileWriter.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)SomeNumber.$(O) SomeNumber.$(C) SomeNumber.$(H): SomeNumber.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticValue.$(H) $(INCLUDE_TOP)\stx\libbasic\Magnitude.$(H) $(INCLUDE_TOP)\stx\libbasic\MetaNumber.$(H) $(INCLUDE_TOP)\stx\libbasic\Number.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)StreamError.$(O) StreamError.$(C) StreamError.$(H): StreamError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)SubclassResponsibilityError.$(O) SubclassResponsibilityError.$(C) SubclassResponsibilityError.$(H): SubclassResponsibilityError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)TimeoutError.$(O) TimeoutError.$(C) TimeoutError.$(H): TimeoutError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)UnimplementedFunctionalityError.$(O) UnimplementedFunctionalityError.$(C) UnimplementedFunctionalityError.$(H): UnimplementedFunctionalityError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)UserPreferences.$(O) UserPreferences.$(C) UserPreferences.$(H): UserPreferences.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
 $(OUTDIR)VarArgCheapBlock.$(O) VarArgCheapBlock.$(C) VarArgCheapBlock.$(H): VarArgCheapBlock.st $(INCLUDE_TOP)\stx\libbasic\Block.$(H) $(INCLUDE_TOP)\stx\libbasic\CheapBlock.$(H) $(INCLUDE_TOP)\stx\libbasic\CompiledCode.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutableFunction.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)WeakIdentityDictionary.$(O) WeakIdentityDictionary.$(C) WeakIdentityDictionary.$(H): WeakIdentityDictionary.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
 $(OUTDIR)WeakValueIdentityDictionary.$(O) WeakValueIdentityDictionary.$(C) WeakValueIdentityDictionary.$(H): WeakValueIdentityDictionary.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(STCHDR)
+$(OUTDIR)AmbiguousMessage.$(O) AmbiguousMessage.$(C) AmbiguousMessage.$(H): AmbiguousMessage.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)ArgumentError.$(O) ArgumentError.$(C) ArgumentError.$(H): ArgumentError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)CannotResumeError.$(O) CannotResumeError.$(C) CannotResumeError.$(H): CannotResumeError.st $(INCLUDE_TOP)\stx\libbasic\ContextError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)CannotReturnError.$(O) CannotReturnError.$(C) CannotReturnError.$(H): CannotReturnError.st $(INCLUDE_TOP)\stx\libbasic\ContextError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)ArithmeticError.$(O) ArithmeticError.$(C) ArithmeticError.$(H): ArithmeticError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)AssertionFailedError.$(O) AssertionFailedError.$(C) AssertionFailedError.$(H): AssertionFailedError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)CharacterEncoderError.$(O) CharacterEncoderError.$(C) CharacterEncoderError.$(H): CharacterEncoderError.st $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)ClassBuildError.$(O) ClassBuildError.$(C) ClassBuildError.$(H): ClassBuildError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)ContextError.$(O) ContextError.$(C) ContextError.$(H): ContextError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DateConversionError.$(O) DateConversionError.$(C) DateConversionError.$(H): DateConversionError.st $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)DomainError.$(O) DomainError.$(C) DomainError.$(H): DomainError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DoubleArray.$(O) DoubleArray.$(C) DoubleArray.$(H): DoubleArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)ElementBoundsError.$(O) ElementBoundsError.$(C) ElementBoundsError.$(H): ElementBoundsError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)EndOfStreamError.$(O) EndOfStreamError.$(C) EndOfStreamError.$(H): EndOfStreamError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)ExternalStream.$(O) ExternalStream.$(C) ExternalStream.$(H): ExternalStream.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadWriteStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
 $(OUTDIR)ExternalStructure.$(O) ExternalStructure.$(C) ExternalStructure.$(H): ExternalStructure.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalBytes.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)FloatArray.$(O) FloatArray.$(C) FloatArray.$(H): FloatArray.st $(INCLUDE_TOP)\stx\libbasic\AbstractNumberVector.$(H) $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)ImmutableByteArray.$(O) ImmutableByteArray.$(C) ImmutableByteArray.$(H): ImmutableByteArray.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\ByteArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)IncompleteNextCountError.$(O) IncompleteNextCountError.$(C) IncompleteNextCountError.$(H): IncompleteNextCountError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
-$(OUTDIR)IndexNotFoundError.$(O) IndexNotFoundError.$(C) IndexNotFoundError.$(H): IndexNotFoundError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidCodeError.$(O) InvalidCodeError.$(C) InvalidCodeError.$(H): InvalidCodeError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidModeError.$(O) InvalidModeError.$(C) InvalidModeError.$(H): InvalidModeError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)InvalidOperationError.$(O) InvalidOperationError.$(C) InvalidOperationError.$(H): InvalidOperationError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)InvalidTypeError.$(O) InvalidTypeError.$(C) InvalidTypeError.$(H): InvalidTypeError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)KeyNotFoundError.$(O) KeyNotFoundError.$(C) KeyNotFoundError.$(H): KeyNotFoundError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)MallocFailure.$(O) MallocFailure.$(C) MallocFailure.$(H): MallocFailure.st $(INCLUDE_TOP)\stx\libbasic\AllocationFailure.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)MessageNotUnderstood.$(O) MessageNotUnderstood.$(C) MessageNotUnderstood.$(H): MessageNotUnderstood.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)MethodNotAppropriateError.$(O) MethodNotAppropriateError.$(C) MethodNotAppropriateError.$(H): MethodNotAppropriateError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)MissingClassInLiteralArrayErrorSignal.$(O) MissingClassInLiteralArrayErrorSignal.$(C) MissingClassInLiteralArrayErrorSignal.$(H): MissingClassInLiteralArrayErrorSignal.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)NoModificationError.$(O) NoModificationError.$(C) NoModificationError.$(H): NoModificationError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)NonBooleanReceiverError.$(O) NonBooleanReceiverError.$(C) NonBooleanReceiverError.$(H): NonBooleanReceiverError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)NotFoundError.$(O) NotFoundError.$(C) NotFoundError.$(H): NotFoundError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)NumberConversionError.$(O) NumberConversionError.$(C) NumberConversionError.$(H): NumberConversionError.st $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)OpenError.$(O) OpenError.$(C) OpenError.$(H): OpenError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)PackageNotFoundError.$(O) PackageNotFoundError.$(C) PackageNotFoundError.$(H): PackageNotFoundError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PackageLoadError.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)PositionError.$(O) PositionError.$(C) PositionError.$(H): PositionError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)PositionOutOfBoundsError.$(O) PositionOutOfBoundsError.$(C) PositionOutOfBoundsError.$(H): PositionOutOfBoundsError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)PrimitiveFailure.$(O) PrimitiveFailure.$(C) PrimitiveFailure.$(H): PrimitiveFailure.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)RangeError.$(O) RangeError.$(C) RangeError.$(H): RangeError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)ReadError.$(O) ReadError.$(C) ReadError.$(H): ReadError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)Registry.$(O) Registry.$(C) Registry.$(H): Registry.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(INCLUDE_TOP)\stx\libbasic\WeakIdentityDictionary.$(H) $(STCHDR)
+$(OUTDIR)SignalError.$(O) SignalError.$(C) SignalError.$(H): SignalError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)SignedByteArray.$(O) SignedByteArray.$(C) SignedByteArray.$(H): SignedByteArray.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\ByteArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)StreamIOError.$(O) StreamIOError.$(C) StreamIOError.$(H): StreamIOError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)StreamNotOpenError.$(O) StreamNotOpenError.$(C) StreamNotOpenError.$(H): StreamNotOpenError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)String.$(O) String.$(C) String.$(H): String.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)SubclassResponsibilityError.$(O) SubclassResponsibilityError.$(C) SubclassResponsibilityError.$(H): SubclassResponsibilityError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)TimeConversionError.$(O) TimeConversionError.$(C) TimeConversionError.$(H): TimeConversionError.st $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)TwoByteString.$(O) TwoByteString.$(C) TwoByteString.$(H): TwoByteString.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
-$(OUTDIR)UnorderedNumbersError.$(O) UnorderedNumbersError.$(C) UnorderedNumbersError.$(H): UnorderedNumbersError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)UnimplementedFunctionalityError.$(O) UnimplementedFunctionalityError.$(C) UnimplementedFunctionalityError.$(H): UnimplementedFunctionalityError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)UnprotectedExternalBytes.$(O) UnprotectedExternalBytes.$(C) UnprotectedExternalBytes.$(H): UnprotectedExternalBytes.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\ExternalBytes.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
 $(OUTDIR)WeakDependencyDictionary.$(O) WeakDependencyDictionary.$(C) WeakDependencyDictionary.$(H): WeakDependencyDictionary.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(INCLUDE_TOP)\stx\libbasic\WeakIdentityDictionary.$(H) $(STCHDR)
 $(OUTDIR)WriteError.$(O) WriteError.$(C) WriteError.$(H): WriteError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
-$(OUTDIR)WrongProceedabilityError.$(O) WrongProceedabilityError.$(C) WrongProceedabilityError.$(H): WrongProceedabilityError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\SignalError.$(H) $(STCHDR)
 $(OUTDIR)AbstractClassInstantiationError.$(O) AbstractClassInstantiationError.$(C) AbstractClassInstantiationError.$(H): AbstractClassInstantiationError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\MethodNotAppropriateError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)BadLiteralsError.$(O) BadLiteralsError.$(C) BadLiteralsError.$(H): BadLiteralsError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\InvalidCodeError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)CachingRegistry.$(O) CachingRegistry.$(C) CachingRegistry.$(H): CachingRegistry.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Registry.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(INCLUDE_TOP)\stx\libbasic\WeakIdentityDictionary.$(H) $(STCHDR)
+$(OUTDIR)CannotResumeError.$(O) CannotResumeError.$(C) CannotResumeError.$(H): CannotResumeError.st $(INCLUDE_TOP)\stx\libbasic\ContextError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)CannotReturnError.$(O) CannotReturnError.$(C) CannotReturnError.$(H): CannotReturnError.st $(INCLUDE_TOP)\stx\libbasic\ContextError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DecodingError.$(O) DecodingError.$(C) DecodingError.$(H): DecodingError.st $(INCLUDE_TOP)\stx\libbasic\CharacterEncoderError.$(H) $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)DomainError.$(O) DomainError.$(C) DomainError.$(H): DomainError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)EncodingError.$(O) EncodingError.$(C) EncodingError.$(H): EncodingError.st $(INCLUDE_TOP)\stx\libbasic\CharacterEncoderError.$(H) $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)FileDoesNotExistException.$(O) FileDoesNotExistException.$(C) FileDoesNotExistException.$(H): FileDoesNotExistException.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OpenError.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)FileStream.$(O) FileStream.$(C) FileStream.$(H): FileStream.st $(INCLUDE_TOP)\stx\libbasic\ExternalStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadWriteStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
 $(OUTDIR)HandleRegistry.$(O) HandleRegistry.$(C) HandleRegistry.$(H): HandleRegistry.st $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Dictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\IdentityDictionary.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\Registry.$(H) $(INCLUDE_TOP)\stx\libbasic\Set.$(H) $(INCLUDE_TOP)\stx\libbasic\WeakIdentityDictionary.$(H) $(STCHDR)
 $(OUTDIR)ImmutableString.$(O) ImmutableString.$(C) ImmutableString.$(H): ImmutableString.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\String.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)IndexNotFoundError.$(O) IndexNotFoundError.$(C) IndexNotFoundError.$(H): IndexNotFoundError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidByteCodeError.$(O) InvalidByteCodeError.$(C) InvalidByteCodeError.$(H): InvalidByteCodeError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\InvalidCodeError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidInstructionError.$(O) InvalidInstructionError.$(C) InvalidInstructionError.$(H): InvalidInstructionError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\InvalidCodeError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)InvalidReadError.$(O) InvalidReadError.$(C) InvalidReadError.$(H): InvalidReadError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)InvalidWriteError.$(O) InvalidWriteError.$(C) InvalidWriteError.$(H): InvalidWriteError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteError.$(H) $(STCHDR)
+$(OUTDIR)KeyNotFoundError.$(O) KeyNotFoundError.$(C) KeyNotFoundError.$(H): KeyNotFoundError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)MissingClassInLiteralArrayErrorSignal.$(O) MissingClassInLiteralArrayErrorSignal.$(C) MissingClassInLiteralArrayErrorSignal.$(H): MissingClassInLiteralArrayErrorSignal.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)NoByteCodeError.$(O) NoByteCodeError.$(C) NoByteCodeError.$(H): NoByteCodeError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\InvalidCodeError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)NonIntegerIndexError.$(O) NonIntegerIndexError.$(C) NonIntegerIndexError.$(H): NonIntegerIndexError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\IndexNotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)NonPositionableExternalStream.$(O) NonPositionableExternalStream.$(C) NonPositionableExternalStream.$(H): NonPositionableExternalStream.st $(INCLUDE_TOP)\stx\libbasic\ExternalStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadWriteStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
 $(OUTDIR)NumberFormatError.$(O) NumberFormatError.$(C) NumberFormatError.$(H): NumberFormatError.st $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NumberConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)OverflowError.$(O) OverflowError.$(C) OverflowError.$(H): OverflowError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\RangeError.$(H) $(STCHDR)
 $(OUTDIR)PTYOpenError.$(O) PTYOpenError.$(C) PTYOpenError.$(H): PTYOpenError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\OpenError.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\StreamError.$(H) $(STCHDR)
 $(OUTDIR)PackageNotCompatibleError.$(O) PackageNotCompatibleError.$(C) PackageNotCompatibleError.$(H): PackageNotCompatibleError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PackageLoadError.$(H) $(INCLUDE_TOP)\stx\libbasic\PackageNotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)SubscriptOutOfBoundsError.$(O) SubscriptOutOfBoundsError.$(C) SubscriptOutOfBoundsError.$(H): SubscriptOutOfBoundsError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\IndexNotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)RangeError.$(O) RangeError.$(C) RangeError.$(H): RangeError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)Symbol.$(O) Symbol.$(C) Symbol.$(H): Symbol.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\String.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
-$(OUTDIR)UnderflowError.$(O) UnderflowError.$(C) UnderflowError.$(H): UnderflowError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\RangeError.$(H) $(STCHDR)
 $(OUTDIR)Unicode16String.$(O) Unicode16String.$(C) Unicode16String.$(H): Unicode16String.st $(INCLUDE_TOP)\stx\libbasic\ArrayedCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\CharacterArray.$(H) $(INCLUDE_TOP)\stx\libbasic\Collection.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\SequenceableCollection.$(H) $(INCLUDE_TOP)\stx\libbasic\TwoByteString.$(H) $(INCLUDE_TOP)\stx\libbasic\UninterpretedBytes.$(H) $(STCHDR)
+$(OUTDIR)UnorderedNumbersError.$(O) UnorderedNumbersError.$(C) UnorderedNumbersError.$(H): UnorderedNumbersError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)WrongNumberOfArgumentsError.$(O) WrongNumberOfArgumentsError.$(C) WrongNumberOfArgumentsError.$(H): WrongNumberOfArgumentsError.st $(INCLUDE_TOP)\stx\libbasic\ArgumentError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
-$(OUTDIR)ZeroDivide.$(O) ZeroDivide.$(C) ZeroDivide.$(H): ZeroDivide.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\DomainError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)WrongProceedabilityError.$(O) WrongProceedabilityError.$(C) WrongProceedabilityError.$(H): WrongProceedabilityError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\SignalError.$(H) $(STCHDR)
 $(OUTDIR)CharacterRangeError.$(O) CharacterRangeError.$(C) CharacterRangeError.$(H): CharacterRangeError.st $(INCLUDE_TOP)\stx\libbasic\CharacterEncoderError.$(H) $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\DecodingError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)DirectoryStream.$(O) DirectoryStream.$(C) DirectoryStream.$(H): DirectoryStream.st $(INCLUDE_TOP)\stx\libbasic\ExternalStream.$(H) $(INCLUDE_TOP)\stx\libbasic\FileStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadWriteStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
 $(OUTDIR)InvalidEncodingError.$(O) InvalidEncodingError.$(C) InvalidEncodingError.$(H): InvalidEncodingError.st $(INCLUDE_TOP)\stx\libbasic\CharacterEncoderError.$(H) $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\DecodingError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)NonIntegerIndexError.$(O) NonIntegerIndexError.$(C) NonIntegerIndexError.$(H): NonIntegerIndexError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\IndexNotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)OverflowError.$(O) OverflowError.$(C) OverflowError.$(H): OverflowError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\RangeError.$(H) $(STCHDR)
 $(OUTDIR)PipeStream.$(O) PipeStream.$(C) PipeStream.$(H): PipeStream.st $(INCLUDE_TOP)\stx\libbasic\ExternalStream.$(H) $(INCLUDE_TOP)\stx\libbasic\NonPositionableExternalStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\PeekableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\PositionableStream.$(H) $(INCLUDE_TOP)\stx\libbasic\ReadWriteStream.$(H) $(INCLUDE_TOP)\stx\libbasic\Stream.$(H) $(INCLUDE_TOP)\stx\libbasic\WriteStream.$(H) $(STCHDR)
 $(OUTDIR)RomanNumberFormatError.$(O) RomanNumberFormatError.$(C) RomanNumberFormatError.$(H): RomanNumberFormatError.st $(INCLUDE_TOP)\stx\libbasic\ConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\NumberConversionError.$(H) $(INCLUDE_TOP)\stx\libbasic\NumberFormatError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)SubscriptOutOfBoundsError.$(O) SubscriptOutOfBoundsError.$(C) SubscriptOutOfBoundsError.$(H): SubscriptOutOfBoundsError.st $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\IndexNotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\NotFoundError.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
+$(OUTDIR)UnderflowError.$(O) UnderflowError.$(C) UnderflowError.$(H): UnderflowError.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(INCLUDE_TOP)\stx\libbasic\RangeError.$(H) $(STCHDR)
+$(OUTDIR)ZeroDivide.$(O) ZeroDivide.$(C) ZeroDivide.$(H): ZeroDivide.st $(INCLUDE_TOP)\stx\libbasic\ArithmeticError.$(H) $(INCLUDE_TOP)\stx\libbasic\DomainError.$(H) $(INCLUDE_TOP)\stx\libbasic\Error.$(H) $(INCLUDE_TOP)\stx\libbasic\Exception.$(H) $(INCLUDE_TOP)\stx\libbasic\ExecutionError.$(H) $(INCLUDE_TOP)\stx\libbasic\GenericException.$(H) $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(INCLUDE_TOP)\stx\libbasic\ProceedableError.$(H) $(STCHDR)
 $(OUTDIR)Win32Process.$(O) Win32Process.$(C) Win32Process.$(H): Win32Process.st $(STCHDR)
 $(OUTDIR)PCFilename.$(O) PCFilename.$(C) PCFilename.$(H): PCFilename.st $(STCHDR)
 $(OUTDIR)Win32Constants.$(O) Win32Constants.$(C) Win32Constants.$(H): Win32Constants.st $(STCHDR)
--- a/libInit.cc	Tue Sep 20 11:37:33 2016 +0100
+++ b/libInit.cc	Mon Oct 03 12:44:41 2016 +0100
@@ -196,9 +196,7 @@
 extern void _CharacterEncoderImplementations__ISO8859_1379_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CharacterEncoderImplementations__KOI8_137U_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CheapBlock_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _ClassBuildError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CmdLineOptionError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _ElementBoundsError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Fraction_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _GetOpt_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _IdentityDictionary_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -244,9 +242,6 @@
 extern void _AbortOperationRequest_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AbstractNumberVector_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AllocationFailure_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _AmbiguousMessage_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _ArithmeticError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _AssertionFailedError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AutoloadMetaclass_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ByteArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CharacterArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -254,7 +249,6 @@
 extern void _Class_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ClassBuildWarning_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ClassLoadInProgressQuery_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _ContextError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ConversionError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DeepCopyError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ExceptionHandlerSet_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -267,9 +261,6 @@
 extern void _InvalidPatchError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _LargeInteger_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _LongFloat_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _MessageNotUnderstood_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _NoModificationError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _NotFoundError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _OSSignalInterrupt_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _OsIllegalOperation_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _OsInaccessibleError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -284,92 +275,101 @@
 extern void _ProceedError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ReadWriteStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ShortFloat_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _SignalError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SmallInteger_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SmalltalkChunkFileSourceWriter_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SomeNumber_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _StreamError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _SubclassResponsibilityError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TimeoutError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _UnimplementedFunctionalityError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _UserPreferences_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _VarArgCheapBlock_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _WeakIdentityDictionary_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _WeakValueIdentityDictionary_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _AmbiguousMessage_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ArgumentError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _CannotResumeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _CannotReturnError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ArithmeticError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _AssertionFailedError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CharacterEncoderError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ClassBuildError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ContextError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DateConversionError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _DomainError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DoubleArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ElementBoundsError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _EndOfStreamError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ExternalStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ExternalStructure_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _FloatArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ImmutableByteArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _IncompleteNextCountError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _IndexNotFoundError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidCodeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidModeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidOperationError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidTypeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _KeyNotFoundError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _MallocFailure_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MessageNotUnderstood_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _MethodNotAppropriateError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _MissingClassInLiteralArrayErrorSignal_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _NoModificationError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _NonBooleanReceiverError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _NotFoundError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _NumberConversionError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _OpenError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PackageNotFoundError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PositionError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PositionOutOfBoundsError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PrimitiveFailure_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _RangeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ReadError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Registry_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SignalError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _SignedByteArray_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _StreamIOError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _StreamNotOpenError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _String_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SubclassResponsibilityError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TimeConversionError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _TwoByteString_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _UnorderedNumbersError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _UnimplementedFunctionalityError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _UnprotectedExternalBytes_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _WeakDependencyDictionary_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _WriteError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _WrongProceedabilityError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _AbstractClassInstantiationError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _BadLiteralsError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CachingRegistry_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _CannotResumeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _CannotReturnError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DecodingError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _DomainError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _EncodingError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _FileDoesNotExistException_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _FileStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _HandleRegistry_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _ImmutableString_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _IndexNotFoundError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidByteCodeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidInstructionError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidReadError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidWriteError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _KeyNotFoundError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _MissingClassInLiteralArrayErrorSignal_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _NoByteCodeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _NonIntegerIndexError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _NonPositionableExternalStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _NumberFormatError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _OverflowError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PTYOpenError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PackageNotCompatibleError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _SubscriptOutOfBoundsError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _RangeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Symbol_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _UnderflowError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _Unicode16String_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _UnorderedNumbersError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _WrongNumberOfArgumentsError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
-extern void _ZeroDivide_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _WrongProceedabilityError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _CharacterRangeError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _DirectoryStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _InvalidEncodingError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _NonIntegerIndexError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _OverflowError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _PipeStream_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _RomanNumberFormatError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _SubscriptOutOfBoundsError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _UnderflowError_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
+extern void _ZeroDivide_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 #ifdef UNIX
 extern void _UnixFileDescriptorHandle_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
 extern void _UnixFileHandle_Init(int pass, struct __vmData__ *__pRT__, OBJ snd);
@@ -582,9 +582,7 @@
     _CharacterEncoderImplementations__ISO8859_1379_Init(pass,__pRT__,snd);
     _CharacterEncoderImplementations__KOI8_137U_Init(pass,__pRT__,snd);
     _CheapBlock_Init(pass,__pRT__,snd);
-    _ClassBuildError_Init(pass,__pRT__,snd);
     _CmdLineOptionError_Init(pass,__pRT__,snd);
-    _ElementBoundsError_Init(pass,__pRT__,snd);
     _Fraction_Init(pass,__pRT__,snd);
     _GetOpt_Init(pass,__pRT__,snd);
     _IdentityDictionary_Init(pass,__pRT__,snd);
@@ -630,9 +628,6 @@
     _AbortOperationRequest_Init(pass,__pRT__,snd);
     _AbstractNumberVector_Init(pass,__pRT__,snd);
     _AllocationFailure_Init(pass,__pRT__,snd);
-    _AmbiguousMessage_Init(pass,__pRT__,snd);
-    _ArithmeticError_Init(pass,__pRT__,snd);
-    _AssertionFailedError_Init(pass,__pRT__,snd);
     _AutoloadMetaclass_Init(pass,__pRT__,snd);
     _ByteArray_Init(pass,__pRT__,snd);
     _CharacterArray_Init(pass,__pRT__,snd);
@@ -640,7 +635,6 @@
     _Class_Init(pass,__pRT__,snd);
     _ClassBuildWarning_Init(pass,__pRT__,snd);
     _ClassLoadInProgressQuery_Init(pass,__pRT__,snd);
-    _ContextError_Init(pass,__pRT__,snd);
     _ConversionError_Init(pass,__pRT__,snd);
     _DeepCopyError_Init(pass,__pRT__,snd);
     _ExceptionHandlerSet_Init(pass,__pRT__,snd);
@@ -653,9 +647,6 @@
     _InvalidPatchError_Init(pass,__pRT__,snd);
     _LargeInteger_Init(pass,__pRT__,snd);
     _LongFloat_Init(pass,__pRT__,snd);
-    _MessageNotUnderstood_Init(pass,__pRT__,snd);
-    _NoModificationError_Init(pass,__pRT__,snd);
-    _NotFoundError_Init(pass,__pRT__,snd);
     _OSSignalInterrupt_Init(pass,__pRT__,snd);
     _OsIllegalOperation_Init(pass,__pRT__,snd);
     _OsInaccessibleError_Init(pass,__pRT__,snd);
@@ -670,92 +661,101 @@
     _ProceedError_Init(pass,__pRT__,snd);
     _ReadWriteStream_Init(pass,__pRT__,snd);
     _ShortFloat_Init(pass,__pRT__,snd);
-    _SignalError_Init(pass,__pRT__,snd);
     _SmallInteger_Init(pass,__pRT__,snd);
     _SmalltalkChunkFileSourceWriter_Init(pass,__pRT__,snd);
     _SomeNumber_Init(pass,__pRT__,snd);
     _StreamError_Init(pass,__pRT__,snd);
-    _SubclassResponsibilityError_Init(pass,__pRT__,snd);
     _TimeoutError_Init(pass,__pRT__,snd);
-    _UnimplementedFunctionalityError_Init(pass,__pRT__,snd);
     _UserPreferences_Init(pass,__pRT__,snd);
     _VarArgCheapBlock_Init(pass,__pRT__,snd);
     _WeakIdentityDictionary_Init(pass,__pRT__,snd);
     _WeakValueIdentityDictionary_Init(pass,__pRT__,snd);
+    _AmbiguousMessage_Init(pass,__pRT__,snd);
     _ArgumentError_Init(pass,__pRT__,snd);
-    _CannotResumeError_Init(pass,__pRT__,snd);
-    _CannotReturnError_Init(pass,__pRT__,snd);
+    _ArithmeticError_Init(pass,__pRT__,snd);
+    _AssertionFailedError_Init(pass,__pRT__,snd);
     _CharacterEncoderError_Init(pass,__pRT__,snd);
+    _ClassBuildError_Init(pass,__pRT__,snd);
+    _ContextError_Init(pass,__pRT__,snd);
     _DateConversionError_Init(pass,__pRT__,snd);
-    _DomainError_Init(pass,__pRT__,snd);
     _DoubleArray_Init(pass,__pRT__,snd);
+    _ElementBoundsError_Init(pass,__pRT__,snd);
     _EndOfStreamError_Init(pass,__pRT__,snd);
     _ExternalStream_Init(pass,__pRT__,snd);
     _ExternalStructure_Init(pass,__pRT__,snd);
     _FloatArray_Init(pass,__pRT__,snd);
     _ImmutableByteArray_Init(pass,__pRT__,snd);
     _IncompleteNextCountError_Init(pass,__pRT__,snd);
-    _IndexNotFoundError_Init(pass,__pRT__,snd);
     _InvalidCodeError_Init(pass,__pRT__,snd);
     _InvalidModeError_Init(pass,__pRT__,snd);
     _InvalidOperationError_Init(pass,__pRT__,snd);
     _InvalidTypeError_Init(pass,__pRT__,snd);
-    _KeyNotFoundError_Init(pass,__pRT__,snd);
     _MallocFailure_Init(pass,__pRT__,snd);
+    _MessageNotUnderstood_Init(pass,__pRT__,snd);
     _MethodNotAppropriateError_Init(pass,__pRT__,snd);
-    _MissingClassInLiteralArrayErrorSignal_Init(pass,__pRT__,snd);
+    _NoModificationError_Init(pass,__pRT__,snd);
     _NonBooleanReceiverError_Init(pass,__pRT__,snd);
+    _NotFoundError_Init(pass,__pRT__,snd);
     _NumberConversionError_Init(pass,__pRT__,snd);
     _OpenError_Init(pass,__pRT__,snd);
     _PackageNotFoundError_Init(pass,__pRT__,snd);
     _PositionError_Init(pass,__pRT__,snd);
     _PositionOutOfBoundsError_Init(pass,__pRT__,snd);
     _PrimitiveFailure_Init(pass,__pRT__,snd);
-    _RangeError_Init(pass,__pRT__,snd);
     _ReadError_Init(pass,__pRT__,snd);
     _Registry_Init(pass,__pRT__,snd);
+    _SignalError_Init(pass,__pRT__,snd);
     _SignedByteArray_Init(pass,__pRT__,snd);
     _StreamIOError_Init(pass,__pRT__,snd);
     _StreamNotOpenError_Init(pass,__pRT__,snd);
     _String_Init(pass,__pRT__,snd);
+    _SubclassResponsibilityError_Init(pass,__pRT__,snd);
     _TimeConversionError_Init(pass,__pRT__,snd);
     _TwoByteString_Init(pass,__pRT__,snd);
-    _UnorderedNumbersError_Init(pass,__pRT__,snd);
+    _UnimplementedFunctionalityError_Init(pass,__pRT__,snd);
     _UnprotectedExternalBytes_Init(pass,__pRT__,snd);
     _WeakDependencyDictionary_Init(pass,__pRT__,snd);
     _WriteError_Init(pass,__pRT__,snd);
-    _WrongProceedabilityError_Init(pass,__pRT__,snd);
     _AbstractClassInstantiationError_Init(pass,__pRT__,snd);
     _BadLiteralsError_Init(pass,__pRT__,snd);
     _CachingRegistry_Init(pass,__pRT__,snd);
+    _CannotResumeError_Init(pass,__pRT__,snd);
+    _CannotReturnError_Init(pass,__pRT__,snd);
     _DecodingError_Init(pass,__pRT__,snd);
+    _DomainError_Init(pass,__pRT__,snd);
     _EncodingError_Init(pass,__pRT__,snd);
     _FileDoesNotExistException_Init(pass,__pRT__,snd);
     _FileStream_Init(pass,__pRT__,snd);
     _HandleRegistry_Init(pass,__pRT__,snd);
     _ImmutableString_Init(pass,__pRT__,snd);
+    _IndexNotFoundError_Init(pass,__pRT__,snd);
     _InvalidByteCodeError_Init(pass,__pRT__,snd);
     _InvalidInstructionError_Init(pass,__pRT__,snd);
     _InvalidReadError_Init(pass,__pRT__,snd);
     _InvalidWriteError_Init(pass,__pRT__,snd);
+    _KeyNotFoundError_Init(pass,__pRT__,snd);
+    _MissingClassInLiteralArrayErrorSignal_Init(pass,__pRT__,snd);
     _NoByteCodeError_Init(pass,__pRT__,snd);
-    _NonIntegerIndexError_Init(pass,__pRT__,snd);
     _NonPositionableExternalStream_Init(pass,__pRT__,snd);
     _NumberFormatError_Init(pass,__pRT__,snd);
-    _OverflowError_Init(pass,__pRT__,snd);
     _PTYOpenError_Init(pass,__pRT__,snd);
     _PackageNotCompatibleError_Init(pass,__pRT__,snd);
-    _SubscriptOutOfBoundsError_Init(pass,__pRT__,snd);
+    _RangeError_Init(pass,__pRT__,snd);
     _Symbol_Init(pass,__pRT__,snd);
-    _UnderflowError_Init(pass,__pRT__,snd);
     _Unicode16String_Init(pass,__pRT__,snd);
+    _UnorderedNumbersError_Init(pass,__pRT__,snd);
     _WrongNumberOfArgumentsError_Init(pass,__pRT__,snd);
-    _ZeroDivide_Init(pass,__pRT__,snd);
+    _WrongProceedabilityError_Init(pass,__pRT__,snd);
     _CharacterRangeError_Init(pass,__pRT__,snd);
     _DirectoryStream_Init(pass,__pRT__,snd);
     _InvalidEncodingError_Init(pass,__pRT__,snd);
+    _NonIntegerIndexError_Init(pass,__pRT__,snd);
+    _OverflowError_Init(pass,__pRT__,snd);
     _PipeStream_Init(pass,__pRT__,snd);
     _RomanNumberFormatError_Init(pass,__pRT__,snd);
+    _SubscriptOutOfBoundsError_Init(pass,__pRT__,snd);
+    _UnderflowError_Init(pass,__pRT__,snd);
+    _ZeroDivide_Init(pass,__pRT__,snd);
 #ifdef UNIX
     _UnixFileDescriptorHandle_Init(pass,__pRT__,snd);
     _UnixFileHandle_Init(pass,__pRT__,snd);
--- a/stx_libbasic.st	Tue Sep 20 11:37:33 2016 +0100
+++ b/stx_libbasic.st	Mon Oct 03 12:44:41 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
 	      All Rights Reserved
@@ -350,9 +352,7 @@
         #'CharacterEncoderImplementations::ISO8859_9'
         #'CharacterEncoderImplementations::KOI8_U'
         CheapBlock
-        ClassBuildError
         CmdLineOptionError
-        ElementBoundsError
         Fraction
         GetOpt
         IdentityDictionary
@@ -401,9 +401,6 @@
         AbortOperationRequest
         AbstractNumberVector
         AllocationFailure
-        AmbiguousMessage
-        ArithmeticError
-        AssertionFailedError
         AutoloadMetaclass
         ByteArray
         CharacterArray
@@ -411,7 +408,6 @@
         Class
         ClassBuildWarning
         ClassLoadInProgressQuery
-        ContextError
         ConversionError
         DeepCopyError
         ExceptionHandlerSet
@@ -424,9 +420,6 @@
         InvalidPatchError
         LargeInteger
         LongFloat
-        MessageNotUnderstood
-        NoModificationError
-        NotFoundError
         OSSignalInterrupt
         (OSXOperatingSystem unix)
         OsIllegalOperation
@@ -442,104 +435,113 @@
         ProceedError
         ReadWriteStream
         ShortFloat
-        SignalError
         SmallInteger
         SmalltalkChunkFileSourceWriter
         SomeNumber
         StreamError
-        SubclassResponsibilityError
         TimeoutError
-        UnimplementedFunctionalityError
         UserPreferences
         VarArgCheapBlock
         WeakIdentityDictionary
         WeakValueIdentityDictionary
+        AmbiguousMessage
         ArgumentError
-        CannotResumeError
-        CannotReturnError
+        ArithmeticError
+        AssertionFailedError
         CharacterEncoderError
+        ClassBuildError
+        ContextError
         DateConversionError
-        DomainError
         DoubleArray
+        ElementBoundsError
         EndOfStreamError
         ExternalStream
         ExternalStructure
         FloatArray
         ImmutableByteArray
         IncompleteNextCountError
-        IndexNotFoundError
         InvalidCodeError
         InvalidModeError
         InvalidOperationError
         InvalidTypeError
-        KeyNotFoundError
         MallocFailure
+        MessageNotUnderstood
         MethodNotAppropriateError
-        MissingClassInLiteralArrayErrorSignal
+        NoModificationError
         NonBooleanReceiverError
+        NotFoundError
         NumberConversionError
         OpenError
         PackageNotFoundError
         PositionError
         PositionOutOfBoundsError
         PrimitiveFailure
-        RangeError
         ReadError
         Registry
+        SignalError
         SignedByteArray
         StreamIOError
         StreamNotOpenError
         String
+        SubclassResponsibilityError
         TimeConversionError
         TwoByteString
-        UnorderedNumbersError
+        UnimplementedFunctionalityError
         UnprotectedExternalBytes
         WeakDependencyDictionary
         WriteError
-        WrongProceedabilityError
         AbstractClassInstantiationError
         BadLiteralsError
         CachingRegistry
+        CannotResumeError
+        CannotReturnError
         DecodingError
+        DomainError
         EncodingError
         FileDoesNotExistException
         FileStream
         HandleRegistry
         ImmutableString
+        IndexNotFoundError
         InvalidByteCodeError
         InvalidInstructionError
         InvalidReadError
         InvalidWriteError
+        KeyNotFoundError
+        MissingClassInLiteralArrayErrorSignal
         NoByteCodeError
-        NonIntegerIndexError
         NonPositionableExternalStream
         NumberFormatError
-        OverflowError
         PTYOpenError
         PackageNotCompatibleError
-        SubscriptOutOfBoundsError
+        RangeError
         Symbol
-        UnderflowError
         Unicode16String
+        UnorderedNumbersError
         WrongNumberOfArgumentsError
-        ZeroDivide
+        WrongProceedabilityError
         CharacterRangeError
         DirectoryStream
         InvalidEncodingError
+        NonIntegerIndexError
+        OverflowError
         PipeStream
         RomanNumberFormatError
-        (SqueakCommentReader autoload)
+        SubscriptOutOfBoundsError
+        UnderflowError
+        ZeroDivide
         (Win32Process win32)
         (PCFilename win32)
         (Win32Constants win32)
         (Win32Handle win32)
-        (SimpleExternalLibraryFunction autoload)
         (Win32FILEHandle win32)
         (Win32OperatingSystem win32)
-        (QualifiedName autoload)
         (OpenVMSFileHandle vms)
         (OpenVMSFilename vms)
         (OpenVMSOperatingSystem vms)
+        (SqueakCommentReader autoload)
+        (SimpleExternalLibraryFunction autoload)
+        (QualifiedName autoload)
         (AbstractDesktop autoload)
         (BadRomanNumberFormatError autoload)
         (#'CharacterEncoderImplementations::BIG5' autoload)
--- a/stx_libbasicWINrc.rc	Tue Sep 20 11:37:33 2016 +0100
+++ b/stx_libbasicWINrc.rc	Mon Oct 03 12:44:41 2016 +0100
@@ -3,7 +3,7 @@
 // automagically generated from the projectDefinition: stx_libbasic.
 //
 VS_VERSION_INFO VERSIONINFO
-  FILEVERSION     7,1,1,161
+  FILEVERSION     7,1,1,163
   PRODUCTVERSION  7,1,0,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
@@ -20,12 +20,12 @@
     BEGIN
       VALUE "CompanyName", "eXept Software AG\0"
       VALUE "FileDescription", "Smalltalk/X Basic Classes (LIB)\0"
-      VALUE "FileVersion", "7.1.1.161\0"
+      VALUE "FileVersion", "7.1.1.163\0"
       VALUE "InternalName", "stx:libbasic\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2012\nCopyright eXept Software AG 2013\0"
       VALUE "ProductName", "Smalltalk/X\0"
       VALUE "ProductVersion", "7.1.0.0\0"
-      VALUE "ProductDate", "Tue, 28 Jun 2016 19:17:02 GMT\0"
+      VALUE "ProductDate", "Tue, 27 Sep 2016 18:13:36 GMT\0"
     END
 
   END