Merged d17dbf11e306 and 3c06d7207200 (branch default - CVS HEAD) jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Thu, 28 Mar 2013 12:21:50 +0000
branchjv
changeset 18042 2aa6ef1820fe
parent 18041 d17dbf11e306 (diff)
parent 14988 3c06d7207200 (current diff)
child 18043 03660093fe98
Merged d17dbf11e306 and 3c06d7207200 (branch default - CVS HEAD)
ApplicationDefinition.st
LibraryDefinition.st
ProjectDefinition.st
Smalltalk.st
SmalltalkChunkFileSourceWriter.st
StandaloneStartup.st
Win32Process.st
--- a/AbortOperationRequest.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/AbortOperationRequest.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 AbortAllOperationRequest subclass:#AbortOperationRequest
@@ -64,7 +63,14 @@
 !AbortOperationRequest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/AbortOperationRequest.st,v 1.5 2005-01-11 17:04:57 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AbortOperationRequest.st,v 1.5 2005/01/11 17:04:57 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: AbortOperationRequest.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 AbortOperationRequest initialize!
+
+
+
--- a/ActivityNotification.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ActivityNotification.st	Thu Mar 28 12:21:50 2013 +0000
@@ -74,7 +74,14 @@
 !ActivityNotification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ActivityNotification.st,v 1.4 2008-10-04 08:42:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ActivityNotification.st,v 1.4 2008/10/04 08:42:14 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: ActivityNotification.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 ActivityNotification initialize!
+
+
+
--- a/AllocationFailure.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/AllocationFailure.st	Thu Mar 28 12:21:50 2013 +0000
@@ -40,9 +40,14 @@
 "
 ! !
 
+
 !AllocationFailure class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/AllocationFailure.st,v 1.6 2013-03-13 23:47:13 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: AllocationFailure.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
--- a/ApplicationDefinition.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ApplicationDefinition.st	Thu Mar 28 12:21:50 2013 +0000
@@ -1863,7 +1863,7 @@
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 %(DEPENDENCIES)
 # ENDMAKEDEPEND --- do not remove this line
-'.
+%(ADDITIONAL_RULES_HG)'.
 
     "Modified: / 22-11-2012 / 17:18:28 / cg"
 !
@@ -2284,6 +2284,8 @@
 
 %(ADDITIONAL_RULES_SVN)
 
+%(ADDITIONAL_RULES_HG)
+
 %(ADDITIONAL_HEADERRULES)
 
 clean::
@@ -2301,6 +2303,7 @@
     "Created: / 29-09-2006 / 23:47:07 / cg"
     "Modified: / 24-06-2009 / 21:40:26 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 26-07-2012 / 00:57:07 / cg"
+    "Modified: / 28-11-2012 / 10:18:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 make_dot_proto_app_source_rules
--- a/ArgumentError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ArgumentError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ExecutionError subclass:#ArgumentError
@@ -44,7 +43,14 @@
 !ArgumentError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ArgumentError.st,v 1.3 2003-09-05 10:27:53 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ArgumentError.st,v 1.3 2003/09/05 10:27:53 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: ArgumentError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 ArgumentError initialize!
+
+
+
--- a/ArithmeticError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ArithmeticError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -40,9 +40,14 @@
 "
 ! !
 
+
 !ArithmeticError class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/ArithmeticError.st,v 1.8 2013-03-13 23:44:07 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: ArithmeticError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
--- a/AspectVisitor.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/AspectVisitor.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Visitor subclass:#AspectVisitor
@@ -131,5 +130,12 @@
 !AspectVisitor class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/AspectVisitor.st,v 1.1 2004-06-11 17:55:26 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AspectVisitor.st,v 1.1 2004/06/11 17:55:26 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: AspectVisitor.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/AssertionFailedError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/AssertionFailedError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -43,5 +43,12 @@
 !AssertionFailedError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/AssertionFailedError.st,v 1.3 2008-09-30 18:09:46 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AssertionFailedError.st,v 1.3 2008/09/30 18:09:46 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: AssertionFailedError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/BadLiteralsError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/BadLiteralsError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 InvalidCodeError subclass:#BadLiteralsError
@@ -50,7 +49,14 @@
 !BadLiteralsError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/BadLiteralsError.st,v 1.4 2003-09-05 10:27:45 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/BadLiteralsError.st,v 1.4 2003/09/05 10:27:45 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: BadLiteralsError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 BadLiteralsError initialize!
+
+
+
--- a/BadRomanNumberFormatError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/BadRomanNumberFormatError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -43,5 +43,8 @@
 !BadRomanNumberFormatError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/BadRomanNumberFormatError.st,v 1.3 2008-08-06 09:52:59 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/BadRomanNumberFormatError.st,v 1.3 2008/08/06 09:52:59 cg Exp $'
 ! !
+
+
+
--- a/Behavior.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Behavior.st	Thu Mar 28 12:21:50 2013 +0000
@@ -300,6 +300,7 @@
 "
 ! !
 
+
 !Behavior class methodsFor:'creating new classes'!
 
 new
@@ -337,8 +338,19 @@
     "Modified: 7.6.1996 / 15:38:58 / stefan"
 ! !
 
+
 !Behavior class methodsFor:'flag bit constants'!
 
+flagAlien
+    "Return the flag code for Alien objects for Translucent Object implementation"
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( __mkSmallInteger(ALIENPOINTERS) );
+%}
+!
+
 flagBehavior
     "return the flag code which marks Behavior-like instances.
      Inline C-code and the VM check this single bit in the flag value when
@@ -800,6 +812,7 @@
 %}
 ! !
 
+
 !Behavior class methodsFor:'helpers'!
 
 classesSortedByLoadOrder:someClasses
@@ -939,6 +952,7 @@
     "Modified: 5.9.1996 / 19:34:41 / cg"
 ! !
 
+
 !Behavior class methodsFor:'misc'!
 
 autoload
@@ -948,6 +962,7 @@
 
 ! !
 
+
 !Behavior class methodsFor:'queries'!
 
 definitionSelectorFirstParts
@@ -1069,6 +1084,7 @@
     ^ self compiledMethodAt:selector
 ! !
 
+
 !Behavior methodsFor:'Compatibility-Squeak'!
 
 classComment:comment stamp:commentStamp
@@ -1121,6 +1137,7 @@
     "Modified (comment): / 20-08-2011 / 16:35:07 / cg"
 ! !
 
+
 !Behavior methodsFor:'Compatibility-VW'!
 
 >> aSelector
@@ -1193,30 +1210,30 @@
     |oldMethod ns selector newLookupObject|
 
     (newSelector isMemberOf:Symbol) ifFalse:[
-	self error:'invalid selector'.
+        self error:'invalid selector'.
     ].
 
     ns := newMethod nameSpace.
     (ns notNil and:[ns ~= self programmingLanguage defaultSelectorNameSpacePrefix]) ifTrue:[
-	selector := (':' , ns , '::' , newSelector) asSymbol.
-	newLookupObject := Smalltalk at: #NamespaceAwareLookup. "/ so it can be nilled to disable that feature
+        selector := (':' , ns , '::' , newSelector) asSymbol.
+        newLookupObject := Smalltalk at: #NamespaceAwareLookup. "/ so it can be nilled to disable that feature
     ] ifFalse:[
-	selector := newSelector
+        selector := newSelector
     ].
 
     "/ Q (cg): isn't that something that the caller should decide?
     oldMethod := self compiledMethodAt:selector.
     oldMethod notNil ifTrue:[
-	newMethod restricted:(oldMethod isRestricted).
-	newMethod setPrivacy:(oldMethod privacy) flushCaches:false.
+        newMethod restricted:(oldMethod isRestricted).
+        newMethod setPrivacy:(oldMethod privacy) flushCaches:false.
     ].
 
     (self primAddSelector:selector withMethod:newMethod) ifFalse:[^ false].
 
     newLookupObject notNil ifTrue:[
-	lookupObject ~= newLookupObject ifTrue:[
-	    self lookupObject: newLookupObject
-	]
+        lookupObject ~= newLookupObject ifTrue:[
+            self lookupObject: newLookupObject
+        ]
     ].
 
     "
@@ -1226,12 +1243,12 @@
     "
 "
     problem: this is slower; since looking for all subclasses is (currently)
-	     a bit slow :-(
-	     We need the hasSubclasses-info bit in Behavior; now
+             a bit slow :-(
+             We need the hasSubclasses-info bit in Behavior; now
 
     self withAllSubclassesDo:[:aClass |
-	ObjectMemory flushInlineCachesFor:aClass withArgs:nargs.
-	ObjectMemory flushMethodCacheFor:aClass
+        ObjectMemory flushInlineCachesFor:aClass withArgs:nargs.
+        ObjectMemory flushMethodCacheFor:aClass
     ].
 "
 
@@ -1351,18 +1368,18 @@
     lookupObject == anObject ifTrue:[^ self ].
     anObject isNil ifTrue:[^self setLookupObject: anObject].
 
-    (anObject respondsTo: #lookupMethodForSelector:directedTo:for:withArguments:from:)
+    (anObject respondsTo: #lookupMethodForSelector:directedTo:for:withArguments:from:ilc:)
     ifFalse:[
-	self error:'Lookup object does not respond to #lookupMethodForSelector:directedTo:for:withArguments:from:'
+        self error:'Lookup object does not respond to #lookupMethodForSelector:directedTo:for:withArguments:from:ilc'
     ].
     (anObject respondsTo:#superLookupObject:)
     ifTrue:[
-	anObject superLookupObject: self lookupObject
+        anObject superLookupObject: self lookupObject
     ].
     self setLookupObject: anObject.
 
     "Created: / 26-04-2010 / 13:35:19 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-    "Modified: / 26-04-2010 / 21:05:39 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 26-10-2011 / 13:00:49 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 methodDictionary
@@ -1424,6 +1441,7 @@
     ^ superclass
 ! !
 
+
 !Behavior methodsFor:'autoload check'!
 
 autoload
@@ -1534,6 +1552,7 @@
     ^ self class syntaxHighlighterClass.
 ! !
 
+
 !Behavior methodsFor:'compiling'!
 
 compile:code notifying:requestor
@@ -1550,6 +1569,7 @@
     "Created: 1.4.1997 / 23:43:43 / stefan"
 ! !
 
+
 !Behavior methodsFor:'copying'!
 
 canCloneFrom:anObject
@@ -1645,6 +1665,7 @@
     ^ self
 ! !
 
+
 !Behavior methodsFor:'dummy changes management'!
 
 addChangeRecordForClassRemove:aClassName
@@ -1657,6 +1678,7 @@
     "Modified: 16.4.1996 / 18:10:35 / cg"
 ! !
 
+
 !Behavior methodsFor:'dummy fileOut'!
 
 fileOutDefinitionOn:aStream
@@ -1669,6 +1691,7 @@
     "Created: 16.4.1996 / 16:28:01 / cg"
 ! !
 
+
 !Behavior methodsFor:'enumerating'!
 
 allDerivedInstancesDo:aBlock
@@ -1939,6 +1962,7 @@
     "
 ! !
 
+
 !Behavior methodsFor:'error handling'!
 
 abstractClassInstantiationError
@@ -1949,6 +1973,7 @@
     "Created: / 02-11-2012 / 10:07:01 / cg"
 ! !
 
+
 !Behavior methodsFor:'initialization'!
 
 deinitialize
@@ -2796,6 +2821,7 @@
     ^ self basicNew:anInteger
 ! !
 
+
 !Behavior methodsFor:'misc'!
 
 browse
@@ -2829,13 +2855,13 @@
     <resource: #programImage>
 
     self isLoaded ifFalse:[
-	^ #autoloadedClassBrowserIcon
+        ^ #autoloadedClassBrowserIcon
     ].
     (self isBrowserStartable) ifTrue:[
-	self isVisualStartable ifTrue:[
-	    ^ #visualStartableClassBrowserIcon
-	].
-	^ #startableClassBrowserIcon
+        self isVisualStartable ifTrue:[
+            ^ #visualStartableClassBrowserIcon
+        ].
+        ^ #startableClassBrowserIcon
     ].
 
     "/ give ruby and other special metaclasses a chance to provide their own icon...
@@ -2860,6 +2886,7 @@
     "Created: / 19.6.1998 / 02:14:02 / cg"
 ! !
 
+
 !Behavior methodsFor:'printing & storing'!
 
 displayOn:aGCOrStream
@@ -2875,7 +2902,7 @@
     "/ what a kludge - Dolphin and Squeak mean: printOn: a stream;
     "/ ST/X (and some old ST80's) mean: draw-yourself on a GC.
     (aGCOrStream isStream) ifFalse:[
-	^ super displayOn:aGCOrStream
+        ^ super displayOn:aGCOrStream
     ].
 
     aGCOrStream nextPutAll:self name
@@ -2885,6 +2912,7 @@
     aStream nextPutAll:(self name).
 ! !
 
+
 !Behavior methodsFor:'private-accessing'!
 
 flags:aNumber
@@ -3015,6 +3043,7 @@
     "Modified: 22.1.1997 / 18:42:12 / cg"
 ! !
 
+
 !Behavior methodsFor:'private-helpers'!
 
 addAllClassVarNamesTo:aCollection
@@ -3080,14 +3109,15 @@
      has to provide a method object for message sends."
 
     lookupObject ~~ aMethodLookupObject ifTrue:[
-	lookupObject := aMethodLookupObject.
-	ObjectMemory flushCachesFor: self.
-	self allSubclassesDo:[:cls|ObjectMemory flushCachesFor: cls]
+        lookupObject := aMethodLookupObject.
+        ObjectMemory flushCachesFor: self.
+        self allSubclassesDo:[:cls|ObjectMemory flushCachesFor: cls]
     ]
 
     "Modified: / 22-07-2010 / 18:10:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !Behavior methodsFor:'queries'!
 
 category
@@ -3393,6 +3423,7 @@
     "Modified: 3.1.1997 / 19:18:49 / cg"
 ! !
 
+
 !Behavior methodsFor:'queries-inheritance'!
 
 allSubclasses
@@ -3481,13 +3512,13 @@
     ^ superclass commonSuperclass:aClass
 
     "
-     Integer commonSuperclass:Fraction
-     SmallInteger commonSuperclass:Fraction
-     View commonSuperclass:Form
-     View commonSuperclass:Image
-     View commonSuperclass:View
-     Integer commonSuperclass:Autoload
-     Integer commonSuperclass:Object
+     Integer commonSuperclass:Fraction             
+     SmallInteger commonSuperclass:Fraction  
+     View commonSuperclass:Form              
+     View commonSuperclass:Image             
+     View commonSuperclass:View              
+     Integer commonSuperclass:Autoload       
+     Integer commonSuperclass:Object         
     "
 
     "Modified (comment): / 17-03-2012 / 19:56:28 / cg"
@@ -3627,7 +3658,7 @@
 
     coll := OrderedCollection new.
     self withAllSuperclassesDo:[:cls |
-	coll add:cls
+        coll add:cls
     ].
     ^ coll
 
@@ -3636,6 +3667,7 @@
     "
 ! !
 
+
 !Behavior methodsFor:'queries-instances'!
 
 allDerivedInstances
@@ -3838,6 +3870,7 @@
     "
 ! !
 
+
 !Behavior methodsFor:'queries-instlayout'!
 
 elementByteSize
@@ -3860,6 +3893,14 @@
 
 !
 
+isAlienBehavior
+    "Returns true iff I'm an alien behavior."
+%{
+    RETURN( ( (INT)(__INST(flags)) & __MASKSMALLINT(ALIENPOINTERS)) ? true : false )
+%}.
+
+!
+
 isBits
     "return true, if instances have indexed byte or short instance variables.
      Ignore long, float and double arrays, since ST-80 code using isBits are probably
@@ -4151,6 +4192,7 @@
 %}
 ! !
 
+
 !Behavior methodsFor:'queries-protocol'!
 
 allSelectors
@@ -4203,12 +4245,13 @@
 
     "JV @ 2010-08-22: Rewritten to respect lookup object."
     (l := self lookupObject) notNil ifTrue:[
-	^ (l
-	    lookupMethodForSelector:aSelector
-	    directedTo:self
-	    for: nil "Fake receiver"
-		withArguments: nil "Fake arguments"
-		from: thisContext sender) notNil
+        ^ (l
+            lookupMethodForSelector:aSelector
+            directedTo:self
+            for: nil "Fake receiver"
+            withArguments: nil "Fake arguments"
+            from: thisContext sender
+            ilc: nil) notNil
     ].
 
     "Original implementation"
@@ -4219,6 +4262,8 @@
      True canUnderstand:#==
      True canUnderstand:#do:
     "
+
+    "Modified: / 28-10-2011 / 09:34:57 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 compiledMethodAt:aSelector
@@ -4298,8 +4343,8 @@
 
     dict := self methodDictionary.
     dict isNil ifTrue:[
-	('Behavior [warning]: nil methodDictionary in ' , self name printString) errorPrintCR.
-	^ exceptionValue value
+        ('Behavior [warning]: nil methodDictionary in ' , self name printString) errorPrintCR.
+        ^ exceptionValue value
     ].
     "Quick check: look into method dictionary"
     mth := dict at: name asSymbol ifAbsent:nil.
@@ -4307,8 +4352,8 @@
 
     "Slow search..."
     dict do: [:each|
-	(each isSynthetic not and:[each name = name])
-	    ifTrue:[^each]
+        (each isSynthetic not and:[each name = name])
+            ifTrue:[^each]
     ].
     ^exceptionValue value
 
@@ -4433,12 +4478,13 @@
 
     "JV @ 2010-08-22: Rewritten to respect lookup object."
     (l := self lookupObject) notNil ifTrue:[
-	^ (l
-	    lookupMethodForSelector:aSelector
-	    directedTo:self
-	    for: nil "Fake receiver"
-		withArguments: nil "Fake arguments"
-		from: thisContext sender)
+        ^ (l
+            lookupMethodForSelector:aSelector
+            directedTo:self
+            for: nil "fake receiver"
+            withArguments: nil "fake arguments"
+            from: thisContext sender
+            ilc: nil "fake ilc")
     ].
 
     cls := self.
@@ -4456,6 +4502,8 @@
 	]
     ].
     ^ nil
+
+    "Modified: / 28-10-2011 / 09:27:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 responseTo:aSelector
@@ -4564,6 +4612,7 @@
     "
 ! !
 
+
 !Behavior methodsFor:'queries-variables'!
 
 allClassVarNames
@@ -4715,8 +4764,8 @@
 !
 
 whichSelectorsRead: instVarName
-	"Answer a set of selectors whose methods read the argument, instVarName,
-	as a named instance variable."
+        "Answer a set of selectors whose methods read the argument, instVarName,
+        as a named instance variable."
 
 "/        | instVarIndex methodDict|
 "/        instVarIndex := self allInstVarNames indexOf: instVarName ifAbsent: [^Set new].
@@ -4724,10 +4773,10 @@
 "/        ^methodDict keys select: [:sel | (methodDict at: sel)
 "/                        readsField: instVarIndex]
 
-	| methodDict |
-	methodDict := self methodDictionary.
-	^ methodDict keys
-	    select: [:sel | (methodDict at: sel) readsInstVar: instVarName]
+        | methodDict |
+        methodDict := self methodDictionary.
+        ^ methodDict keys 
+            select: [:sel | (methodDict at: sel) readsInstVar: instVarName]
 
     "Modified: / 23-07-2012 / 11:22:04 / cg"
 !
@@ -4785,22 +4834,23 @@
 !
 
 whichSelectorsWrite: instVarName
-	"Answer a set of selectors whose methods write the argument, instVarName,
-	as a named instance variable."
+        "Answer a set of selectors whose methods write the argument, instVarName,
+        as a named instance variable."
 
 "/        | instVarIndex methodDict |
 "/        instVarIndex := self allInstVarNames indexOf: instVarName ifAbsent: [^Set new].
 "/        methodDict := self methodDictionary.
 "/        ^methodDict keys select: [:sel | (methodDict at: sel)
 "/                        writesField: instVarIndex]
-	| methodDict |
-	methodDict := self methodDictionary.
-	^ methodDict keys
-	    select: [:sel | (methodDict at: sel) writesInstVar: instVarName]
+        | methodDict |
+        methodDict := self methodDictionary.
+        ^ methodDict keys 
+            select: [:sel | (methodDict at: sel) writesInstVar: instVarName]
 
     "Modified: / 23-07-2012 / 11:21:17 / cg"
 ! !
 
+
 !Behavior methodsFor:'snapshots'!
 
 postSnapshot
@@ -4819,6 +4869,7 @@
     "Modified: 16.4.1996 / 18:12:14 / cg"
 ! !
 
+
 !Behavior methodsFor:'tracing'!
 
 traceInto:aRequestor level:level from:referrer
@@ -4829,6 +4880,7 @@
 
 ! !
 
+
 !Behavior methodsFor:'visiting'!
 
 acceptVisitor:aVisitor with:aParameter
@@ -4836,6 +4888,7 @@
     ^ aVisitor visitBehavior:self with:aParameter
 ! !
 
+
 !Behavior class methodsFor:'documentation'!
 
 version
--- a/BreakPointInterrupt.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/BreakPointInterrupt.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 HaltInterrupt subclass:#BreakPointInterrupt
@@ -45,5 +44,12 @@
 !BreakPointInterrupt class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/BreakPointInterrupt.st,v 1.3 2003-08-29 19:18:16 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/BreakPointInterrupt.st,v 1.3 2003/08/29 19:18:16 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: BreakPointInterrupt.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/CachingRegistry.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CachingRegistry.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,7 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
+"{ Package: 'stx:libbasic' }"
 
 Registry subclass:#CachingRegistry
 	instanceVariableNames:'keptReferences cacheSize'
@@ -92,5 +92,12 @@
 !CachingRegistry class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CachingRegistry.st,v 1.1 1999-07-22 23:17:43 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CachingRegistry.st,v 1.1 1999/07/22 23:17:43 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CachingRegistry.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/CannotResumeError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CannotResumeError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ContextError subclass:#CannotResumeError
@@ -47,5 +46,12 @@
 !CannotResumeError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CannotResumeError.st,v 1.4 2003-08-29 19:21:21 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CannotResumeError.st,v 1.4 2003/08/29 19:21:21 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CannotResumeError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/CannotReturnError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CannotReturnError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ContextError subclass:#CannotReturnError
@@ -47,5 +46,12 @@
 !CannotReturnError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CannotReturnError.st,v 1.4 2003-08-29 19:21:05 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CannotReturnError.st,v 1.4 2003/08/29 19:21:05 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CannotReturnError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/CharacterEncoder.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoder.st	Thu Mar 28 12:21:50 2013 +0000
@@ -213,6 +213,7 @@
 "
 ! !
 
+
 !CharacterEncoder class methodsFor:'instance creation'!
 
 encoderFor:encodingNameSymbol
@@ -518,6 +519,7 @@
     "Modified: / 12-07-2012 / 19:45:15 / cg"
 ! !
 
+
 !CharacterEncoder class methodsFor:'Compatibility-ST80'!
 
 encoderNamed: encoderName
@@ -537,12 +539,14 @@
     "Modified: 20.6.1997 / 17:38:40 / cg"
 ! !
 
+
 !CharacterEncoder class methodsFor:'accessing'!
 
 nullEncoderInstance
     ^ NullEncoderInstance
 ! !
 
+
 !CharacterEncoder class methodsFor:'class initialization'!
 
 initialize
@@ -563,7 +567,7 @@
 
     "/ className decoded-name array-of-encodingNames
     #(
-        (ASCII              unicode     ( ascii 'us-ascii' 'iso-ir-6' 'ibm-367' 'ms-cp367' 'cp367'  'iso646-us' 'ibm-cp367' ))
+        (ASCII              unicode     ( ascii 'us-ascii' 'iso-ir-6' 'ibm-367' 'ms-cp367' 'cp367'  'iso646-us' 'ibm-cp367' 'ansi_x3.4-1968' ))
 
         (BIG5               unicode     ( big5 ))
 
@@ -706,13 +710,20 @@
         ].
     ].
 
+    OperatingSystem isUNIXlike ifTrue:[
+        "/Initialize OS system encoder
+        OperatingSystem getCodesetEncoder.
+    ].
+
     "
      self initialize
     "
 
     "Modified: / 01-04-2011 / 14:30:06 / cg"
+    "Modified (format): / 23-01-2013 / 09:56:53 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !CharacterEncoder class methodsFor:'constants'!
 
 jis7KanjiEscapeSequence
@@ -758,6 +769,7 @@
     ^ JisISO2022EscapeSequence.
 ! !
 
+
 !CharacterEncoder class methodsFor:'encoding & decoding'!
 
 decode:aCodePoint
@@ -869,6 +881,7 @@
     "
 ! !
 
+
 !CharacterEncoder class methodsFor:'private'!
 
 flushCode
@@ -886,6 +899,7 @@
     "
 ! !
 
+
 !CharacterEncoder class methodsFor:'private-mapping setup'!
 
 generateCode
@@ -936,6 +950,7 @@
     ^ 'http://std.dkuug.dk/i18n/charmaps/' , rel
 ! !
 
+
 !CharacterEncoder class methodsFor:'queries'!
 
 isEncoding:subSetEncodingArg subSetOf:superSetEncodingArg
@@ -1039,6 +1054,7 @@
     ^ self nameOfEncoding asUppercaseFirst
 ! !
 
+
 !CharacterEncoder class methodsFor:'testing'!
 
 isAbstract
@@ -1049,6 +1065,7 @@
     ^ self == CharacterEncoder
 ! !
 
+
 !CharacterEncoder class methodsFor:'utilities'!
 
 guessEncodingOfBuffer:buffer
@@ -1234,6 +1251,7 @@
     "
 ! !
 
+
 !CharacterEncoder methodsFor:'encoding & decoding'!
 
 decode:anEncoding
@@ -1310,6 +1328,7 @@
     ^ newString
 ! !
 
+
 !CharacterEncoder methodsFor:'error handling'!
 
 decodingError 
@@ -1366,6 +1385,7 @@
     "Modified: / 12-07-2012 / 20:36:37 / cg"
 ! !
 
+
 !CharacterEncoder methodsFor:'printing'!
 
 printOn:aStream
@@ -1375,12 +1395,14 @@
         nextPutAll:(self nameOfEncoding)
 ! !
 
+
 !CharacterEncoder methodsFor:'private'!
 
 newString:size
     self subclassResponsibility
 ! !
 
+
 !CharacterEncoder methodsFor:'queries'!
 
 characterSize:codePoint
@@ -1410,6 +1432,7 @@
     ^ self class userFriendlyNameOfEncoding
 ! !
 
+
 !CharacterEncoder methodsFor:'stream support'!
 
 readNext:charactersToRead charactersFrom:stream 
@@ -1435,6 +1458,7 @@
     ^ aStream next
 ! !
 
+
 !CharacterEncoder::CompoundEncoder class methodsFor:'documentation'!
 
 documentation
@@ -1454,6 +1478,7 @@
 "
 ! !
 
+
 !CharacterEncoder::CompoundEncoder methodsFor:'accessing'!
 
 encoder:encoderArg decoder:decoderArg  
@@ -1463,6 +1488,7 @@
     encoder := encoderArg.
 ! !
 
+
 !CharacterEncoder::CompoundEncoder methodsFor:'encoding & decoding'!
 
 decode:aCode
@@ -1481,6 +1507,7 @@
     ^ encoder encodeString:(decoder decodeString:aString)
 ! !
 
+
 !CharacterEncoder::CompoundEncoder methodsFor:'printing'!
 
 printOn:aStream
@@ -1493,6 +1520,7 @@
     encoder printOn:aStream
 ! !
 
+
 !CharacterEncoder::DefaultEncoder class methodsFor:'documentation'!
 
 documentation
@@ -1501,6 +1529,7 @@
 "
 ! !
 
+
 !CharacterEncoder::InverseEncoder class methodsFor:'documentation'!
 
 documentation
@@ -1510,12 +1539,14 @@
 "
 ! !
 
+
 !CharacterEncoder::InverseEncoder methodsFor:'accessing'!
 
 decoder:something
     decoder := something.
 ! !
 
+
 !CharacterEncoder::InverseEncoder methodsFor:'encoding & decoding'!
 
 decode:aCode
@@ -1534,6 +1565,7 @@
     ^ decoder decodeString:aString
 ! !
 
+
 !CharacterEncoder::InverseEncoder methodsFor:'printing'!
 
 printOn:aStream
@@ -1543,18 +1575,21 @@
         nextPutAll:(decoder nameOfDecodedCode)
 ! !
 
+
 !CharacterEncoder::InverseEncoder methodsFor:'queries'!
 
 characterSize:charOrcodePoint
     ^ decoder characterSize:charOrcodePoint
 ! !
 
+
 !CharacterEncoder::InverseEncoder methodsFor:'stream support'!
 
 readNextInputCharacterFrom:aStream
     ^ decoder readNextInputCharacterFrom:aStream
 ! !
 
+
 !CharacterEncoder::NullEncoder class methodsFor:'documentation'!
 
 documentation
@@ -1563,6 +1598,7 @@
 "
 ! !
 
+
 !CharacterEncoder::NullEncoder methodsFor:'encoding & decoding'!
 
 decode:aCode
@@ -1581,12 +1617,14 @@
     ^ aString
 ! !
 
+
 !CharacterEncoder::NullEncoder methodsFor:'queries'!
 
 isNullEncoder
     ^ true
 ! !
 
+
 !CharacterEncoder::OtherEncoding class methodsFor:'private'!
 
 flushCode
@@ -1595,6 +1633,7 @@
 generateEncoderCode
 ! !
 
+
 !CharacterEncoder::TwoStepEncoder class methodsFor:'documentation'!
 
 documentation
@@ -1607,6 +1646,7 @@
 "
 ! !
 
+
 !CharacterEncoder::TwoStepEncoder methodsFor:'accessing'!
 
 encoder1:encoder1Arg encoder2:encoder2Arg
@@ -1616,6 +1656,7 @@
     encoder2 := encoder2Arg.
 ! !
 
+
 !CharacterEncoder::TwoStepEncoder methodsFor:'encoding & decoding'!
 
 decode:aCode
@@ -1634,6 +1675,7 @@
     ^ encoder2 encodeString:(encoder1 encodeString:aString)
 ! !
 
+
 !CharacterEncoder::TwoStepEncoder methodsFor:'printing'!
 
 printOn:aStream
@@ -1645,6 +1687,7 @@
         nextPutAll:(encoder2 nameOfEncoding)
 ! !
 
+
 !CharacterEncoder::TwoStepEncoder methodsFor:'queries'!
 
 characterSize:codePoint
@@ -1674,6 +1717,7 @@
 
 ! !
 
+
 !CharacterEncoder class methodsFor:'documentation'!
 
 version
@@ -1682,6 +1726,11 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoder.st,v 1.122 2013-03-20 10:37:05 cg Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/CharacterEncoderError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -65,5 +65,12 @@
 !CharacterEncoderError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderError.st,v 1.9 2008-10-30 19:54:05 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderError.st,v 1.9 2008/10/30 19:54:05 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CharacterEncoderError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__ASCII.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__ASCII.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -241,5 +240,12 @@
 !ASCII class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ASCII.st,v 1.4 2005-03-31 18:12:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ASCII.st,v 1.4 2005/03/31 18:12:07 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CharacterEncoderImplementations__ASCII.st 10807 2012-05-05 21:58:24Z vranyj1 $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__BIG5.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__BIG5.st	Thu Mar 28 12:21:50 2013 +0000
@@ -52,5 +52,8 @@
 !BIG5 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__BIG5.st,v 1.3 2004-03-09 21:59:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__BIG5.st,v 1.3 2004/03/09 21:59:35 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__CNS11643.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__CNS11643.st	Thu Mar 28 12:21:50 2013 +0000
@@ -46,5 +46,8 @@
 !CNS11643 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__CNS11643.st,v 1.3 2004-03-09 21:59:27 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__CNS11643.st,v 1.3 2004/03/09 21:59:27 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__CP437.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__CP437.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -933,5 +932,9 @@
 !CP437 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__CP437.st,v 1.4 2005-03-31 18:12:18 cg Exp $'
+    ^ '$Id: CharacterEncoderImplementations__CP437.st 10842 2012-09-07 10:49:18Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id:: CharacterEncoderImplementations__CP437.st 10842 2012-09-07 10:49:18Z vranyj1                                           $'
 ! !
--- a/CharacterEncoderImplementations__GB2313_1980.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__GB2313_1980.st	Thu Mar 28 12:21:50 2013 +0000
@@ -52,5 +52,8 @@
 !GB2313_1980 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__GB2313_1980.st,v 1.3 2004-03-09 21:57:26 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__GB2313_1980.st,v 1.3 2004/03/09 21:57:26 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__HANGUL.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__HANGUL.st	Thu Mar 28 12:21:50 2013 +0000
@@ -46,5 +46,8 @@
 !HANGUL class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__HANGUL.st,v 1.3 2004-03-09 21:57:59 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__HANGUL.st,v 1.3 2004/03/09 21:57:59 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__ISO10646_1.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__ISO10646_1.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -64,5 +63,12 @@
 !ISO10646_1 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ISO10646_1.st,v 1.4 2004-03-09 22:00:08 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ISO10646_1.st,v 1.4 2004/03/09 22:00:08 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CharacterEncoderImplementations__ISO10646_1.st 10807 2012-05-05 21:58:24Z vranyj1 $'
 ! !
+
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CharacterEncoderImplementations__ISO10646_to_JavaText.st	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,153 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libbasic' }"
+
+"{ NameSpace: CharacterEncoderImplementations }"
+
+TwoByteEncoder subclass:#ISO10646_to_JavaText
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Collections-Text-Encodings'
+!
+
+!ISO10646_to_JavaText class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    Translates \uXXXX-escapes in the text
+"
+! !
+
+!ISO10646_to_JavaText methodsFor:'encoding & decoding'!
+
+decode:aCode
+    self shouldNotImplement "/ no single byte conversion possible
+!
+
+decodeString:aStringOrByteCollection
+    "given a string in JavaText encoding (i.e. with \uXXXX escaped characters),
+     return a new string containing the same characters, in 16bit (or more) encoding.
+     Returns either a normal String, a TwoByteString or a FourByteString instance.
+     Only useful, when reading Java property and resource files.
+     This only handles up-to 30bit characters."
+
+    |nBits ch 
+     in out codePoint t|
+
+    nBits := 8.
+    in := aStringOrByteCollection readStream.
+    out := WriteStream on:(String new:10).
+    [in atEnd] whileFalse:[
+        ch := in next.
+        ch == $\ ifTrue:[
+            in peekOrNil == $u ifTrue:[
+                in next.
+                codePoint := 0.
+                4 timesRepeat:[
+                    ch := in peekOrNil.
+                    codePoint := (codePoint * 16) + ch digitValue.
+                    in next.
+                ].
+                codePoint > 16rFF ifTrue:[
+                    codePoint > 16rFFFF ifTrue:[
+                        nBits < 32 ifTrue:[
+                            t := out contents.
+                            out := WriteStream on:(Unicode32String fromString:t).
+                            out position:t size.
+                            nBits := 32.
+                        ]
+                    ] ifFalse:[
+                        nBits < 16 ifTrue:[
+                            t := out contents.
+                            out := WriteStream on:(Unicode16String fromString:t).
+                            out position:t size.
+                            nBits := 16.
+                        ]
+                    ]
+                ].
+                out nextPut:(Character value:codePoint).
+            ] ifFalse:[
+                out nextPut:ch
+            ]
+        ] ifFalse:[
+            out nextPut:ch
+        ].
+    ].
+    ^ out contents
+
+    "
+     CharacterEncoderImplementations::ISO10646_to_JavaText
+        decodeString:'AB\u1234CD' 
+    "
+
+    "Modified: / 23-10-2006 / 13:23:18 / cg"
+!
+
+encode:aCode
+    self shouldNotImplement "/ no single byte conversion possible
+!
+
+encodeString:aUnicodeString
+    "return the JavaText representation of aUnicodeString.
+     The resulting string is only useful to be stored on some external file,
+     not for being used inside ST/X."
+
+    |ch in out codePoint|
+
+    in := aUnicodeString readStream.
+    out := WriteStream on:(String new:10).
+    [in atEnd] whileFalse:[
+        ch := in next.
+        codePoint := ch codePoint.
+        (codePoint between:16r20 and:16r7F) ifTrue:[
+            out nextPut:ch.
+        ] ifFalse:[
+            out nextPutAll:'\u'.
+            out nextPutAll:((codePoint printStringRadix:16) leftPaddedTo:4 with:$0).
+        ].
+    ].
+    ^ out contents
+
+    "
+     CharacterEncoderImplementations::ISO10646_to_JavaText
+        encodeString:'hello '  
+
+     CharacterEncoderImplementations::ISO10646_to_JavaText
+        decodeString:(CharacterEncoderImplementations::ISO10646_to_JavaText encodeString:'hello ') 
+    "
+
+    "Modified: / 23-10-2006 / 13:25:03 / cg"
+! !
+
+!ISO10646_to_JavaText class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JavaText.st,v 1.1 2006/10/23 11:25:58 cg Exp $'
+! !
+
+
+
--- a/CharacterEncoderImplementations__ISO10646_to_SGML.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__ISO10646_to_SGML.st	Thu Mar 28 12:21:50 2013 +0000
@@ -145,7 +145,7 @@
 
     "
      CharacterEncoderImplementations::ISO10646_to_SGML
-        encodeString:'hello äöü' 
+        encodeString:'hello ' 
     "
 
     "Modified: / 23-10-2006 / 13:25:27 / cg"
@@ -154,5 +154,8 @@
 !ISO10646_to_SGML class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ISO10646_to_SGML.st,v 1.3 2006-10-23 11:25:11 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ISO10646_to_SGML.st,v 1.3 2006/10/23 11:25:11 cg Exp $'
 ! !
+
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CharacterEncoderImplementations__ISO10646_to_XMLUTF8.st	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,190 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libbasic' }"
+
+"{ NameSpace: CharacterEncoderImplementations }"
+
+ISO10646_to_UTF8 subclass:#ISO10646_to_XMLUTF8
+	instanceVariableNames:''
+	classVariableNames:'ReplacementCharacter'
+	poolDictionaries:''
+	category:'Collections-Text-Encodings'
+!
+
+!ISO10646_to_XMLUTF8 class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    This encoder encodes characters into utf8 characters that may
+    occur in XML document.
+
+    Not all UTF characters are valid in XML, whatever encoding
+    is used. For a reference, see 
+
+      http://www.w3.org/TR/2000/REC-xml-20001006#NT-Char   
+
+    Invalid characters are replaced by ReplacementCharacter
+    with $? as default.
+
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz>
+
+    [instance variables:]
+
+    [class variables:]
+
+    [see also:]
+        http://www.w3.org/TR/2000/REC-xml-20001006#NT-Char
+
+"
+! !
+
+!ISO10646_to_XMLUTF8 class methodsFor:'initialization'!
+
+initialize
+    "Invoked at system start or when the class is dynamically loaded."
+
+    ReplacementCharacter := $?.
+
+    "Modified: / 30-06-2012 / 19:55:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!ISO10646_to_XMLUTF8 methodsFor:'encoding & decoding'!
+
+encodeString:aUnicodeString
+    "return the UTF-8 representation of a aUnicodeString.
+     The resulting string contains only valid XML unicode
+     characters. Invalid characters are replaced by a
+     ReplacementCharacter. For details, please see
+
+     http://www.w3.org/TR/2000/REC-xml-20001006#NT-Char
+
+    "
+
+    |s|
+
+    "Copy-paste of superclass's method and tweaked. Not ideal, but
+     but avoids 1 string copy"
+
+    s := WriteStream on:(String uninitializedNew:aUnicodeString size).
+    aUnicodeString do:[:eachCharacter |
+        |codePoint b1 b2 b3 b4 b5 v "{Class: SmallInteger }"|
+
+        codePoint := eachCharacter codePoint.
+        (self isValidXMLunicode: codePoint) ifFalse:[
+            codePoint := ReplacementCharacter codePoint.
+        ].
+
+        codePoint <= 16r7F ifTrue:[
+            s nextPut:(Character value:codePoint).
+        ] ifFalse:[
+            b1 := Character value:((codePoint bitAnd:16r3F) bitOr:2r10000000).
+            v := codePoint bitShift:-6.
+            v <= 16r1F ifTrue:[
+                s nextPut:(Character value:(v bitOr:2r11000000)).
+                s nextPut:b1.
+            ] ifFalse:[
+                b2 := Character value:((v bitAnd:16r3F) bitOr:2r10000000).
+                v := v bitShift:-6.
+                v <= 16r0F ifTrue:[
+                    s nextPut:(Character value:(v bitOr:2r11100000)).
+                    s nextPut:b2; nextPut:b1.
+                ] ifFalse:[
+                    b3 := Character value:((v bitAnd:16r3F) bitOr:2r10000000).
+                    v := v bitShift:-6.
+                    v <= 16r07 ifTrue:[
+                        s nextPut:(Character value:(v bitOr:2r11110000)).
+                        s nextPut:b3; nextPut:b2; nextPut:b1.
+                    ] ifFalse:[
+                        b4 := Character value:((v bitAnd:16r3F) bitOr:2r10000000).
+                        v := v bitShift:-6.
+                        v <= 16r03 ifTrue:[
+                            s nextPut:(Character value:(v bitOr:2r11111000)).
+                            s nextPut:b4; nextPut:b3; nextPut:b2; nextPut:b1.
+                        ] ifFalse:[
+                            b5 := Character value:((v bitAnd:16r3F) bitOr:2r10000000).
+                            v := v bitShift:-6.
+                            v <= 16r01 ifTrue:[
+                                s nextPut:(Character value:(v bitOr:2r11111100)).
+                                s nextPut:b5; nextPut:b4; nextPut:b3; nextPut:b2; nextPut:b1.
+                            ] ifFalse:[
+                                "/ cannot happen - we only support up to 30 bit characters
+                                self error:'ascii value > 31bit in utf8Encode'.
+                            ]
+                        ].
+                    ].
+                ].
+            ].
+        ].
+    ].
+
+    ^ s contents
+
+    "
+     (self encodeString:'hello') asByteArray                             #[104 101 108 108 111]
+     (self encodeString:(Character value:16r40) asString) asByteArray    #[64]
+     (self encodeString:(Character value:16r7F) asString) asByteArray    #[127]
+     (self encodeString:(Character value:16r80) asString) asByteArray    #[194 128]
+     (self encodeString:(Character value:16rFF) asString) asByteArray    #[195 191]
+     (self encodeString:(Character value:16r100) asString) asByteArray   #[196 128]
+     (self encodeString:(Character value:16r200) asString) asByteArray   #[200 128]
+     (self encodeString:(Character value:16r400) asString) asByteArray   #[208 128]
+     (self encodeString:(Character value:16r800) asString) asByteArray   #[224 160 128]
+     (self encodeString:(Character value:16r1000) asString) asByteArray  #[225 128 128]
+     (self encodeString:(Character value:16r2000) asString) asByteArray  #[226 128 128]
+     (self encodeString:(Character value:16r4000) asString) asByteArray  #[228 128 128]
+     (self encodeString:(Character value:16r8000) asString) asByteArray  #[232 128 128]
+     (self encodeString:(Character value:16rFFFF) asString) asByteArray  #[239 191 191]
+    "
+
+    "Created: / 30-06-2012 / 20:07:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!ISO10646_to_XMLUTF8 methodsFor:'queries'!
+
+isValidXMLunicode: codePoint
+    "Returns true, if given codePoint (Integer!!!!!!) is
+     valid XML unicode."
+
+    codePoint == 16r0009 ifTrue:[ ^ true ].
+    codePoint == 16r000A ifTrue:[ ^ true ].
+    codePoint == 16r000D ifTrue:[ ^ true ].
+    (codePoint between: 16r0020  and: 16rD7FF  ) ifTrue:[ ^ true ].
+    (codePoint between: 16rE000  and: 16rFFFD  ) ifTrue:[ ^ true ].
+    (codePoint between: 16r10000 and: 16r10FFFF) ifTrue:[ ^ true ].
+
+    ^false.
+
+    "Created: / 30-06-2012 / 20:11:16 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
+!ISO10646_to_XMLUTF8 class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id::                                                                                                                        $'
+! !
+
+ISO10646_to_XMLUTF8 initialize!
--- a/CharacterEncoderImplementations__ISO8859_11.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__ISO8859_11.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -596,5 +595,9 @@
 !ISO8859_11 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ISO8859_11.st,v 1.4 2005-03-31 18:12:32 cg Exp $'
+    ^ '$Id: CharacterEncoderImplementations__ISO8859_11.st 10842 2012-09-07 10:49:18Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id:: CharacterEncoderImplementations__ISO8859_11.st 10842 2012-09-07 10:49:18Z vranyj1                                      $'
 ! !
--- a/CharacterEncoderImplementations__ISO8859_2.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__ISO8859_2.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -766,5 +765,12 @@
 !ISO8859_2 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ISO8859_2.st,v 1.4 2005-03-31 18:12:47 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__ISO8859_2.st,v 1.4 2005/03/31 18:12:47 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CharacterEncoderImplementations__ISO8859_2.st 10807 2012-05-05 21:58:24Z vranyj1 $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__JIS0201.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__JIS0201.st	Thu Mar 28 12:21:50 2013 +0000
@@ -558,5 +558,8 @@
 !JIS0201 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0201.st,v 1.3 2004-03-09 21:59:06 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0201.st,v 1.3 2004/03/09 21:59:06 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__JIS0208.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__JIS0208.st	Thu Mar 28 12:21:50 2013 +0000
@@ -28646,5 +28646,8 @@
 !JIS0208 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0208.st,v 1.4 2008-10-30 19:54:58 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0208.st,v 1.4 2008/10/30 19:54:58 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__JIS0208_to_EUC.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__JIS0208_to_EUC.st	Thu Mar 28 12:21:50 2013 +0000
@@ -332,5 +332,8 @@
 !JIS0208_to_EUC class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0208_to_EUC.st,v 1.4 2005-07-08 17:15:01 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0208_to_EUC.st,v 1.4 2005/07/08 17:15:01 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__JIS0208_to_JIS7.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__JIS0208_to_JIS7.st	Thu Mar 28 12:21:50 2013 +0000
@@ -372,5 +372,8 @@
 !JIS0208_to_JIS7 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0208_to_JIS7.st,v 1.7 2004-03-12 09:15:11 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0208_to_JIS7.st,v 1.7 2004/03/12 09:15:11 ca Exp $'
 ! !
+
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/CharacterEncoderImplementations__JIS0208_to_SJIS.st	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,354 @@
+"
+ COPYRIGHT (c) 2004 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+"{ Package: 'stx:libbasic' }"
+
+"{ NameSpace: CharacterEncoderImplementations }"
+
+TwoByteEncoder subclass:#JIS0208_to_SJIS
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Collections-Text-Encodings'
+!
+
+!JIS0208_to_SJIS class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2004 by eXept Software AG
+              All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+! !
+
+!JIS0208_to_SJIS class methodsFor:'mapping'!
+
+mapFileURL1_relativePathName
+    ^ 'OBSOLETE/EASTASIA/JIS/SHIFTJIS.TXT'
+! !
+
+!JIS0208_to_SJIS class methodsFor:'queries'!
+
+nameOfDecodedCode
+    "I encode sjis into jis"
+
+    ^ #'jis0208'
+! !
+
+!JIS0208_to_SJIS methodsFor:'encoding & decoding'!
+
+decodeString:aString
+    "return a new JIS-Encoded-String containing the characters from aString,
+     which are interpreted as Shift-JIS encoded singleByte chars.
+     Shift-JIS is a leadyByte code, with a variable-length encoding."
+
+    |newString char1 char2
+     sz         "{ Class: SmallInteger }"
+     dstIdx     "{ Class: SmallInteger }"
+     srcIdx     "{ Class: SmallInteger }"
+     b1         "{ Class: SmallInteger }"
+     b2         "{ Class: SmallInteger }"
+     val        "{ Class: SmallInteger }"
+     any16bit romans|
+
+    sz := aString size.
+    sz == 0 ifTrue:[^ aString].
+
+    newString := TwoByteString new:sz.
+    any16bit := false.
+    dstIdx := 1.
+    srcIdx := 1.
+
+    romans := CharacterEncoderImplementations::JIS0208 romanTable.
+
+%{
+    if (__isStringLike(aString)
+     && (__Class(newString) == @global(TwoByteString))) {
+        INT _dstIdx = 0, _srcIdx = 0;
+        int _sz = __intVal(sz);
+        unsigned char *_cp = __stringVal(aString);
+        unsigned char _c1, _c2;
+        unsigned short *_jcp = (unsigned short *)__stringVal(newString);
+
+        while (_srcIdx < _sz) {
+            int _val;
+
+            _c1 = _cp[_srcIdx];
+            _srcIdx++;
+
+            if ((_srcIdx < _sz)
+             && (((_c1 >= 129) && (_c1 <= 159))
+                 || ((_c1 >= 224) && (_c1 <= 239)))) {
+                _c2 = _cp[_srcIdx];
+                _srcIdx++;
+                if ((_c2 >= 64) && (_c2 <= 252)) {
+                    int _adjust, _rowOffs, _cellOffs;
+                    int _b1, _b2;
+
+                    _adjust = (_c2 < 159) ? 1 : 0;
+                    _rowOffs = (_c1 < 160) ? 112 : 176;
+                    if (_adjust) {
+                        _cellOffs = 31 + ((_c2 > 127) ? 1 : 0);
+                    } else {
+                        _cellOffs = 126;
+                    }
+                    _b1 = ((_c1 - _rowOffs) << 1) - _adjust;
+                    _b2 = (_c2 - _cellOffs);
+                    _val = (_b1<<8) + _b2;
+                    if (_val <= 0) {
+                        /* decoder error - let smalltalk handle that */
+                        _srcIdx -= 2;
+                        goto getOutOfHere;
+                    }
+                    if (_val > 0xFF) any16bit = true;
+                    _jcp[_dstIdx] = _val;
+                } else {
+                    /* mhmh - append untranslated */
+
+                    _jcp[_dstIdx] = _c1;
+                    _dstIdx++;
+                    _jcp[_dstIdx] = _c2;
+                }
+            } else {
+                if ((_c1 >= 0xA1 /* 161 */) && (_c1 <= 0xDF /* 223 */)) {
+                    /* HALFWIDTH KATAKANA
+                     * map half-width katakana to 8E:xx
+                     */
+                    _val = _c1 - 128;
+                    _val = _val + 0x8E00;
+                    any16bit = true;
+                    _jcp[_dstIdx] = _val;
+                } else {
+                    /* roman characters are translated as per romanTable */
+                    _jcp[_dstIdx] = _c1;
+                    if ((romans != nil) 
+                     && (__isArray(romans))
+                     && ((_c1 - 0x20) < __arraySize(romans))) {
+                        any16bit = true;
+                        _jcp[_dstIdx] = __intVal(__ArrayInstPtr(romans)->a_element[(_c1 - 0x20)]);
+                    }
+                }
+            }
+            _dstIdx++;
+        }
+    getOutOfHere: ;
+        dstIdx = __mkSmallInteger(_dstIdx+1);
+        srcIdx = __mkSmallInteger(_srcIdx+1);
+    }
+%}.
+
+    [srcIdx <= sz] whileTrue:[
+        "/
+        "/ scan for next character in 129..159 or 224..239
+        "/
+        char1 := aString at:srcIdx.
+        srcIdx := srcIdx + 1.
+        b1 := char1 codePoint.
+
+        ((srcIdx <= sz) 
+        and:[(b1 >= 16r81"129" and:[b1 <= 16r9F"159"])                 "/ SJIS1 81 .. 9F
+             or:[b1 >= 16rE0"224" and:[b1 <= 16rEF"239"]]]) ifTrue:[   "/       E0 .. EF
+            char2 := aString at:srcIdx.
+            srcIdx := srcIdx + 1.
+            b2 := char2 codePoint.
+            (b2 >= 16r40"64" and:[b2 <= 16rFC"252"]) ifTrue:[          "/ SJIS2 40 .. FC
+                |adjust rowOffs cellOffs|
+
+                adjust := (b2 < 16r9F"159") ifTrue:[1] ifFalse:[0].
+                rowOffs := b1 < 16rA0"160" ifTrue:[112] ifFalse:[176].
+                adjust == 1 ifTrue:[
+                    cellOffs := 31 + (b2 > 127 ifTrue:[1] ifFalse:[0]).
+                ] ifFalse:[
+                    cellOffs := 126.
+                ].
+                b1 := ((b1 - rowOffs) bitShift:1) - adjust.
+                b2 := (b2 - cellOffs).
+                val := (b1 bitShift:8) + b2.
+                val <= 0 ifTrue:[
+                    DecodingError
+                            raiseWith:aString
+                            errorString:'SJIS decoding failed (not SJIS encoded ?)'.
+                    newString at:dstIdx put:char1.
+                    dstIdx := dstIdx + 1.
+                    newString at:dstIdx put:char2.
+                ] ifFalse:[
+                    val > 16rFF ifTrue:[any16bit := true].
+                    newString at:dstIdx put:(Character value:val).
+                ]
+            ] ifFalse:[
+                "/ mhmh - append untranslated
+
+                newString at:dstIdx put:char1.
+                dstIdx := dstIdx + 1.
+                newString at:dstIdx put:char2.
+            ]
+        ] ifFalse:[    
+            (b1 >= 16rA1 "161" and:[b1 <= 16rDF "223"]) ifTrue:[     "/ HALFWIDTH KATAKANA
+                "/ map half-width katakan to 8E:xx
+                val := b1 - 128.
+                val := val + (16r8E"142" bitShift:8).
+                any16bit := true.
+                newString at:dstIdx put:(Character value:val).
+            ] ifFalse:[    
+                "/ roman characters translated as per romanTable
+                newString at:dstIdx put:char1
+                romans isArray ifTrue:[
+                    char1 codePoint < romans size ifTrue:[
+                        any16bit := true.
+                        newString at:dstIdx put:(Character value:(romans at:char1 codePoint-32+1)).
+                    ]
+                ]
+            ]
+        ].
+        dstIdx := dstIdx + 1.
+    ].
+    any16bit ifFalse:[
+        newString := String fromString:newString 
+    ].
+
+    (dstIdx-1) ~~ sz ifTrue:[
+        newString := newString copyTo:dstIdx - 1.
+    ].
+
+    ^ newString
+
+    "simple:
+
+     CharacterEncoderImplementations::JIS0208_to_SJIS decodeString:'hello'  
+     (CharacterEncoder encoderFor:#sjis) decodeString:'hello'         
+
+     CharacterEncoderImplementations::JIS0208_to_SJIS decodeString:('../../doc/online/japanese/TOP.html' asFilename contents asString)  
+
+     '../../doc/online/japanese/TOP.html' asFilename contents asString
+                decodeFrom:#sjis  
+    "
+!
+
+encodeString:aJISString
+    "return a new string with aJISStrings characters as SJIS encoded 8bit string.
+     The resulting string is only useful to be stored on some external file,
+     not for being displayed in an ST/X view."
+
+    |sz "{ Class: SmallInteger }"
+     rval "{ Class: SmallInteger }"
+     val  "{ Class: SmallInteger }"
+     romans c out isSJIS|
+
+    romans := JIS0208 romanTable.
+
+    sz := aJISString size.
+    sz == 0 ifTrue:[^ ''].
+
+    out := WriteStream on:(String new:(sz * 2)).
+
+    1 to:sz do:[:srcIndex |
+        val := (c := aJISString at:srcIndex) codePoint.
+        (val <= 128) ifTrue:[
+            "/ a control or ascii character    
+            out nextPut:c.
+        ] ifFalse:[
+            (val == 16rFFFF "invalid-char") ifTrue:[
+                out nextPut:Character space.
+            ] ifFalse:[
+                (val > 150 and:[val < 224]) ifTrue:[
+                    "/ ascii subset
+                    out nextPut:c.
+                ] ifFalse:[
+                    "/ should not happen ...
+                    val <= 255 ifTrue:[
+                        out nextPut:c.
+                    ] ifFalse:[
+                        isSJIS := true.
+
+                        "/ check for HALFWIDTH KATAKANA
+                        "/ 8E:xx
+                        "/ NO: halfwidth katakana no longer generated
+                        "/     remains there as full-width katakana
+
+"/                        (val bitAnd:16rFF00) == 16r8E00 ifTrue:[
+"/                            |b|
+"/
+"/                            b := (val bitAnd:16rFF) + 128.
+"/                            (b >= 16rA1 "161" and:[b <= 16rDF "223"]) ifTrue:[
+"/                                out nextPut:(Character value:b).
+"/                                isSJIS := false.
+"/                            ].
+"/                        ].
+
+                        isSJIS ifTrue:[
+                            "/ check for a roman character
+                            (val between:"romanTable min" 16r2121 and:"romanTable max" 16r2573) ifTrue:[
+                                rval := romans indexOf:val.
+                                rval ~~ 0 ifTrue:[
+                                    rval := rval - 1 + 32.
+                                    rval <= 16r7F ifTrue:[ "/ do not translate halfwidth katakana
+                                        out nextPut:(Character value:rval).
+                                        isSJIS := false.
+                                    ]
+                                ].
+                            ].
+                        ].
+
+                        isSJIS ifTrue:[
+                            |b1 b2 rowOffset cellOffset|
+
+                            b1 := (val bitShift:-8).
+                            b2 := (val bitAnd:16rFF).
+                            rowOffset := (b1 < 95) ifTrue:[112] ifFalse:[176].
+                            cellOffset := b1 odd ifTrue:[(b2 > 95) ifTrue:[32] ifFalse:[31]]
+                                                 ifFalse:[126].
+
+                            out nextPut:(Character value:(((b1 + 1) bitShift:-1) + rowOffset)).
+                            out nextPut:(Character value:b2 + cellOffset).
+                        ]
+                    ]
+                ]
+            ]
+        ].
+    ].
+    ^ out contents
+! !
+
+!JIS0208_to_SJIS methodsFor:'private'!
+
+newString:size
+    ^ JISEncodedString new:size
+! !
+
+!JIS0208_to_SJIS methodsFor:'queries'!
+
+nameOfEncoding
+    ^ #'sjis'
+! !
+
+!JIS0208_to_SJIS class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__SJIS.st,v 1.12 2009/11/05 16:26:27 stefan Exp $'
+!
+
+version_CVS
+    ^ '§Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__SJIS.st,v 1.12 2009/11/05 16:26:27 stefan Exp §'
+!
+
+version_SVN
+    ^ '$Id: CharacterEncoderImplementations__JIS0208_to_SJIS.st 10807 2012-05-05 21:58:24Z vranyj1 $'
+! !
+
+
+
--- a/CharacterEncoderImplementations__JIS0212.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__JIS0212.st	Thu Mar 28 12:21:50 2013 +0000
@@ -46,5 +46,8 @@
 !JIS0212 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0212.st,v 1.3 2004-03-09 21:58:52 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JIS0212.st,v 1.3 2004/03/09 21:58:52 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__JOHAB.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__JOHAB.st	Thu Mar 28 12:21:50 2013 +0000
@@ -46,5 +46,8 @@
 !JOHAB class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JOHAB.st,v 1.3 2004-03-09 21:57:37 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JOHAB.st,v 1.3 2004/03/09 21:57:37 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__JavaText.st	Wed Mar 27 20:36:15 2013 +0100
+++ /dev/null	Thu Jan 01 00:00:00 1970 +0000
@@ -1,150 +0,0 @@
-"
- COPYRIGHT (c) 2006 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-"{ Package: 'stx:libbasic' }"
-
-"{ NameSpace: CharacterEncoderImplementations }"
-
-TwoByteEncoder subclass:#ISO10646_to_JavaText
-	instanceVariableNames:''
-	classVariableNames:''
-	poolDictionaries:''
-	category:'Collections-Text-Encodings'
-!
-
-!ISO10646_to_JavaText class methodsFor:'documentation'!
-
-copyright
-"
- COPYRIGHT (c) 2006 by eXept Software AG
-              All Rights Reserved
-
- This software is furnished under a license and may be used
- only in accordance with the terms of that license and with the
- inclusion of the above copyright notice.   This software may not
- be provided or otherwise made available to, or used by, any
- other person.  No title to or ownership of the software is
- hereby transferred.
-"
-!
-
-documentation
-"
-    Translates \uXXXX-escapes in the text
-"
-! !
-
-!ISO10646_to_JavaText methodsFor:'encoding & decoding'!
-
-decode:aCode
-    self shouldNotImplement "/ no single byte conversion possible
-!
-
-decodeString:aStringOrByteCollection
-    "given a string in JavaText encoding (i.e. with \uXXXX escaped characters),
-     return a new string containing the same characters, in 16bit (or more) encoding.
-     Returns either a normal String, a TwoByteString or a FourByteString instance.
-     Only useful, when reading Java property and resource files.
-     This only handles up-to 30bit characters."
-
-    |nBits ch 
-     in out codePoint t|
-
-    nBits := 8.
-    in := aStringOrByteCollection readStream.
-    out := WriteStream on:(String new:10).
-    [in atEnd] whileFalse:[
-        ch := in next.
-        ch == $\ ifTrue:[
-            in peekOrNil == $u ifTrue:[
-                in next.
-                codePoint := 0.
-                4 timesRepeat:[
-                    ch := in peekOrNil.
-                    codePoint := (codePoint * 16) + ch digitValue.
-                    in next.
-                ].
-                codePoint > 16rFF ifTrue:[
-                    codePoint > 16rFFFF ifTrue:[
-                        nBits < 32 ifTrue:[
-                            t := out contents.
-                            out := WriteStream on:(Unicode32String fromString:t).
-                            out position:t size.
-                            nBits := 32.
-                        ]
-                    ] ifFalse:[
-                        nBits < 16 ifTrue:[
-                            t := out contents.
-                            out := WriteStream on:(Unicode16String fromString:t).
-                            out position:t size.
-                            nBits := 16.
-                        ]
-                    ]
-                ].
-                out nextPut:(Character value:codePoint).
-            ] ifFalse:[
-                out nextPut:ch
-            ]
-        ] ifFalse:[
-            out nextPut:ch
-        ].
-    ].
-    ^ out contents
-
-    "
-     CharacterEncoderImplementations::ISO10646_to_JavaText
-        decodeString:'AB\u1234CD' 
-    "
-
-    "Modified: / 23-10-2006 / 13:23:18 / cg"
-!
-
-encode:aCode
-    self shouldNotImplement "/ no single byte conversion possible
-!
-
-encodeString:aUnicodeString
-    "return the JavaText representation of aUnicodeString.
-     The resulting string is only useful to be stored on some external file,
-     not for being used inside ST/X."
-
-    |ch in out codePoint|
-
-    in := aUnicodeString readStream.
-    out := WriteStream on:(String new:10).
-    [in atEnd] whileFalse:[
-        ch := in next.
-        codePoint := ch codePoint.
-        (codePoint between:16r20 and:16r7F) ifTrue:[
-            out nextPut:ch.
-        ] ifFalse:[
-            out nextPutAll:'\u'.
-            out nextPutAll:((codePoint printStringRadix:16) leftPaddedTo:4 with:$0).
-        ].
-    ].
-    ^ out contents
-
-    "
-     CharacterEncoderImplementations::ISO10646_to_JavaText
-        encodeString:'hello äöü'  
-
-     CharacterEncoderImplementations::ISO10646_to_JavaText
-        decodeString:(CharacterEncoderImplementations::ISO10646_to_JavaText encodeString:'hello äöü') 
-    "
-
-    "Modified: / 23-10-2006 / 13:25:03 / cg"
-! !
-
-!ISO10646_to_JavaText class methodsFor:'documentation'!
-
-version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__JavaText.st,v 1.1 2006-10-23 11:25:58 cg Exp $'
-! !
--- a/CharacterEncoderImplementations__KSC5601.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__KSC5601.st	Thu Mar 28 12:21:50 2013 +0000
@@ -46,5 +46,8 @@
 !KSC5601 class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__KSC5601.st,v 1.3 2004-03-09 21:58:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__KSC5601.st,v 1.3 2004/03/09 21:58:35 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Arabic.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Arabic.st	Thu Mar 28 12:21:50 2013 +0000
@@ -584,5 +584,8 @@
 !MAC_Arabic class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Arabic.st,v 1.3 2004-03-09 21:59:43 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Arabic.st,v 1.3 2004/03/09 21:59:43 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_CentralEuropean.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_CentralEuropean.st	Thu Mar 28 12:21:50 2013 +0000
@@ -373,5 +373,8 @@
 !MAC_CentralEuropean class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_CentralEuropean.st,v 1.3 2004-03-09 21:57:41 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_CentralEuropean.st,v 1.3 2004/03/09 21:57:41 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Croatian.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Croatian.st	Thu Mar 28 12:21:50 2013 +0000
@@ -399,5 +399,8 @@
 !MAC_Croatian class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Croatian.st,v 1.3 2004-03-09 22:00:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Croatian.st,v 1.3 2004/03/09 22:00:00 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Cyrillic.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Cyrillic.st	Thu Mar 28 12:21:50 2013 +0000
@@ -398,5 +398,8 @@
 !MAC_Cyrillic class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Cyrillic.st,v 1.3 2004-03-09 21:57:56 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Cyrillic.st,v 1.3 2004/03/09 21:57:56 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Dingbats.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Dingbats.st	Thu Mar 28 12:21:50 2013 +0000
@@ -375,5 +375,8 @@
 !MAC_Dingbats class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Dingbats.st,v 1.3 2004-03-09 22:01:02 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Dingbats.st,v 1.3 2004/03/09 22:01:02 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Farsi.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Farsi.st	Thu Mar 28 12:21:50 2013 +0000
@@ -569,5 +569,8 @@
 !MAC_Farsi class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Farsi.st,v 1.3 2004-03-09 22:00:02 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Farsi.st,v 1.3 2004/03/09 22:00:02 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Greek.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Greek.st	Thu Mar 28 12:21:50 2013 +0000
@@ -847,5 +847,8 @@
 !MAC_Greek class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Greek.st,v 1.3 2004-03-09 21:59:52 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Greek.st,v 1.3 2004/03/09 21:59:52 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Hebrew.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Hebrew.st	Thu Mar 28 12:21:50 2013 +0000
@@ -611,5 +611,8 @@
 !MAC_Hebrew class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Hebrew.st,v 1.3 2004-03-09 22:01:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Hebrew.st,v 1.3 2004/03/09 22:01:14 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Iceland.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Iceland.st	Thu Mar 28 12:21:50 2013 +0000
@@ -417,5 +417,8 @@
 !MAC_Iceland class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Iceland.st,v 1.3 2004-03-09 21:59:24 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Iceland.st,v 1.3 2004/03/09 21:59:24 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Japanese.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Japanese.st	Thu Mar 28 12:21:50 2013 +0000
@@ -46,5 +46,8 @@
 !MAC_Japanese class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Japanese.st,v 1.3 2004-03-09 21:59:58 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Japanese.st,v 1.3 2004/03/09 21:59:58 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Korean.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Korean.st	Thu Mar 28 12:21:50 2013 +0000
@@ -46,5 +46,8 @@
 !MAC_Korean class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Korean.st,v 1.3 2004-03-09 21:58:29 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Korean.st,v 1.3 2004/03/09 21:58:29 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Romanian.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Romanian.st	Thu Mar 28 12:21:50 2013 +0000
@@ -414,5 +414,8 @@
 !MAC_Romanian class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Romanian.st,v 1.3 2004-03-09 21:58:05 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Romanian.st,v 1.3 2004/03/09 21:58:05 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Symbol.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Symbol.st	Thu Mar 28 12:21:50 2013 +0000
@@ -445,5 +445,8 @@
 !MAC_Symbol class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Symbol.st,v 1.3 2004-03-09 21:57:44 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Symbol.st,v 1.3 2004/03/09 21:57:44 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Thai.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Thai.st	Thu Mar 28 12:21:50 2013 +0000
@@ -432,5 +432,8 @@
 !MAC_Thai class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Thai.st,v 1.3 2004-03-09 21:59:00 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Thai.st,v 1.3 2004/03/09 21:59:00 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MAC_Turkish.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MAC_Turkish.st	Thu Mar 28 12:21:50 2013 +0000
@@ -389,5 +389,8 @@
 !MAC_Turkish class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Turkish.st,v 1.3 2004-03-09 21:59:55 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MAC_Turkish.st,v 1.3 2004/03/09 21:59:55 cg Exp $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MS_Arabic.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MS_Arabic.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -839,5 +838,9 @@
 !MS_Arabic class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Arabic.st,v 1.4 2005-03-31 18:48:44 cg Exp $'
+    ^ '$Id: CharacterEncoderImplementations__MS_Arabic.st 10842 2012-09-07 10:49:18Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id:: CharacterEncoderImplementations__MS_Arabic.st 10842 2012-09-07 10:49:18Z vranyj1                                       $'
 ! !
--- a/CharacterEncoderImplementations__MS_Baltic.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MS_Baltic.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -852,5 +851,12 @@
 !MS_Baltic class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Baltic.st,v 1.4 2005-03-31 18:48:58 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Baltic.st,v 1.4 2005/03/31 18:48:58 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CharacterEncoderImplementations__MS_Baltic.st 10807 2012-05-05 21:58:24Z vranyj1 $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MS_Cyrillic.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MS_Cyrillic.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -718,5 +717,12 @@
 !MS_Cyrillic class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Cyrillic.st,v 1.4 2005-03-31 18:48:53 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Cyrillic.st,v 1.4 2005/03/31 18:48:53 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CharacterEncoderImplementations__MS_Cyrillic.st 10807 2012-05-05 21:58:24Z vranyj1 $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MS_EastEuropean.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MS_EastEuropean.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -813,5 +812,9 @@
 !MS_EastEuropean class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_EastEuropean.st,v 1.4 2005-03-31 18:48:47 cg Exp $'
+    ^ '$Id: CharacterEncoderImplementations__MS_EastEuropean.st 10842 2012-09-07 10:49:18Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id:: CharacterEncoderImplementations__MS_EastEuropean.st 10842 2012-09-07 10:49:18Z vranyj1                                 $'
 ! !
--- a/CharacterEncoderImplementations__MS_Greek.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MS_Greek.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -671,5 +670,12 @@
 !MS_Greek class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Greek.st,v 1.4 2005-03-31 18:49:01 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Greek.st,v 1.4 2005/03/31 18:49:01 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CharacterEncoderImplementations__MS_Greek.st 10807 2012-05-05 21:58:24Z vranyj1 $'
 ! !
+
+
+
--- a/CharacterEncoderImplementations__MS_Hebrew.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MS_Hebrew.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -607,5 +606,9 @@
 !MS_Hebrew class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Hebrew.st,v 1.4 2005-03-31 18:48:50 cg Exp $'
+    ^ '$Id: CharacterEncoderImplementations__MS_Hebrew.st 10842 2012-09-07 10:49:18Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id:: CharacterEncoderImplementations__MS_Hebrew.st 10842 2012-09-07 10:49:18Z vranyj1                                       $'
 ! !
--- a/CharacterEncoderImplementations__MS_Symbol.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MS_Symbol.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -88,5 +87,9 @@
 !MS_Symbol class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Symbol.st,v 1.5 2005-03-31 18:48:55 cg Exp $'
+    ^ '$Id: CharacterEncoderImplementations__MS_Symbol.st 10842 2012-09-07 10:49:18Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id:: CharacterEncoderImplementations__MS_Symbol.st 10842 2012-09-07 10:49:18Z vranyj1                                       $'
 ! !
--- a/CharacterEncoderImplementations__MS_Turkish.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__MS_Turkish.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 "{ NameSpace: CharacterEncoderImplementations }"
@@ -819,5 +818,9 @@
 !MS_Turkish class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__MS_Turkish.st,v 1.5 2005-03-31 18:49:37 cg Exp $'
+    ^ '$Id: CharacterEncoderImplementations__MS_Turkish.st 10842 2012-09-07 10:49:18Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id:: CharacterEncoderImplementations__MS_Turkish.st 10842 2012-09-07 10:49:18Z vranyj1                                      $'
 ! !
--- a/CharacterEncoderImplementations__NEXT.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterEncoderImplementations__NEXT.st	Thu Mar 28 12:21:50 2013 +0000
@@ -313,5 +313,8 @@
 !NEXT class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__NEXT.st,v 1.3 2004-03-09 22:00:52 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterEncoderImplementations__NEXT.st,v 1.3 2004/03/09 22:00:52 cg Exp $'
 ! !
+
+
+
--- a/CharacterRangeError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CharacterRangeError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 DecodingError subclass:#CharacterRangeError
@@ -38,5 +37,12 @@
 !CharacterRangeError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CharacterRangeError.st,v 1.2 2004-03-09 21:58:39 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CharacterRangeError.st,v 1.2 2004/03/09 21:58:39 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CharacterRangeError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/CheapBlock.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/CheapBlock.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Block variableSubclass:#CheapBlock
@@ -182,5 +181,12 @@
 !CheapBlock class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/CheapBlock.st,v 1.20 2000-04-01 13:05:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/CheapBlock.st,v 1.20 2000/04/01 13:05:54 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: CheapBlock.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/Class.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Class.st	Thu Mar 28 12:21:50 2013 +0000
@@ -21,7 +21,7 @@
 	category:'Kernel-Classes'
 !
 
-Array variableSubclass:#ArrayWithSequenceNumberValidation
+Array subclass:#ArrayWithSequenceNumberValidation
 	instanceVariableNames:'sequenceNumber'
 	classVariableNames:''
 	poolDictionaries:''
@@ -141,6 +141,7 @@
 "
 ! !
 
+
 !Class class methodsFor:'accessing-flags'!
 
 tryLocalSourceFirst
@@ -189,6 +190,7 @@
     ^ UpdatingChanges
 ! !
 
+
 !Class class methodsFor:'creating new classes'!
 
 name:newName
@@ -296,6 +298,7 @@
     "Created: / 08-11-2010 / 16:08:25 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !Class class methodsFor:'helpers'!
 
 nameWithoutPrefix:name
@@ -308,10 +311,10 @@
 
     idx := name lastIndexOf:$:.
     [idx > 1 and:[ (name at:(idx-1)) ~~ $: ]] whileTrue:[
-	idx := name lastIndexOf:$: startingAt:idx-2.
+        idx := name lastIndexOf:$: startingAt:idx-2.
     ].
     idx == 0 ifTrue:[
-	^ name
+        ^ name
     ].
 
     ^ name copyFrom:idx+1.
@@ -344,10 +347,10 @@
     "/ care for standAlone apps which have no CVS (libbasic3) included
     "/
     mgr isNil ifTrue:[
-	AbstractSourceCodeManager notNil ifTrue:[
-	    ^ CVSVersionInfo fromRCSString:aString
-	].
-	^ nil
+        AbstractSourceCodeManager notNil ifTrue:[
+            ^ CVSVersionInfo fromRCSString:aString 
+        ].
+        ^ nil
     ].
     ^ mgr revisionInfoFromString:aString.
 
@@ -385,6 +388,7 @@
     "Modified: / 22-10-2008 / 20:29:50 / cg"
 ! !
 
+
 !Class class methodsFor:'misc'!
 
 template:aCategoryString
@@ -399,6 +403,7 @@
     "Created: / 19.6.1998 / 02:09:06 / cg"
 ! !
 
+
 !Class class methodsFor:'private'!
 
 flushSubclassInfo
@@ -425,7 +430,7 @@
      This is private protocol"
 
     aClass notNil ifTrue:[
-	aClass flushSubclasses
+        aClass flushSubclasses
     ].
 
     "
@@ -435,6 +440,7 @@
     "Modified: / 06-12-2011 / 16:20:49 / cg"
 ! !
 
+
 !Class class methodsFor:'queries'!
 
 isBuiltInClass
@@ -502,20 +508,21 @@
     "Modified: / 18.3.1999 / 18:16:11 / stefan"
 ! !
 
+
 !Class methodsFor:'Compatibility-ST/V and V''Age'!
 
 defaultCategoryForSTVorVAGEClasses
     |cat app|
 
     DefaultApplicationQuerySignal isHandled ifTrue:[
-	app := DefaultApplicationQuerySignal query.
-	app notNil ifTrue:[
-	    cat := "'Applications-' ," app nameWithoutPrefix.
-	] ifFalse:[
-	    cat := DefaultCategoryForVAGE ? 'V''Age classes'.
-	].
+        app := DefaultApplicationQuerySignal query.
+        app notNil ifTrue:[
+            cat := "'Applications-' ," app nameWithoutPrefix.
+        ] ifFalse:[
+            cat := DefaultCategoryForVAGE ? 'V''Age classes'.
+        ].
     ] ifFalse:[
-	cat := DefaultCategoryForSTV ? 'ST/V classes'.
+        cat := DefaultCategoryForSTV ? 'ST/V classes'.
     ].
 
     ^ cat
@@ -529,12 +536,12 @@
     "this method allows fileIn of ST/V and V'Age classes"
 
     ^ self
-	   subclass:nm
-	   instanceVariableNames:iV
-	   classVariableNames:cV
-	   poolDictionaries:p
-	   category:(self defaultCategoryForSTVorVAGEClasses)
-	   classInstanceVariableNames:cIV
+           subclass:nm
+           instanceVariableNames:iV
+           classVariableNames:cV
+           poolDictionaries:p
+           category:(self defaultCategoryForSTVorVAGEClasses)
+           classInstanceVariableNames:cIV
 !
 
 subclass:t instanceVariableNames:f classVariableNames:d poolDictionaries:s
@@ -612,6 +619,7 @@
 	   category:(self defaultCategoryForSTVorVAGEClasses)
 ! !
 
+
 !Class methodsFor:'Compatibility-ST80'!
 
 classPool
@@ -643,6 +651,7 @@
     "Created: / 18.6.1998 / 22:08:45 / cg"
 ! !
 
+
 !Class methodsFor:'accessing'!
 
 addClassVarName:aString
@@ -953,7 +962,7 @@
     "/ (e at:self nameWithoutNamespacePrefix ifAbsent:nil)
     "/ or
     (Smalltalk at:name ifAbsent:nil) == self ifFalse:[
-	^ nil
+        ^ nil
     ].
     ^ e
 !
@@ -1030,21 +1039,21 @@
 
     "/ cached in environment
     environment isNil ifTrue:[
-	e := Smalltalk. "/ default
-
-	name notNil ifTrue:[
-	    "/ due to the implementation, extract this from my name
-	    "/ (physically, all classes are found in Smalltalk)
-
-	    idx := name lastIndexOf:$:.
-	    idx ~~ 0 ifTrue:[
-		(name at:idx-1) == $: ifTrue:[
-		    nsName := name copyTo:(idx - 2).
-		    e := Smalltalk at:nsName asSymbol.
-		]
-	    ].
-	].
-	environment := e.
+        e := Smalltalk. "/ default
+
+        name notNil ifTrue:[
+            "/ due to the implementation, extract this from my name
+            "/ (physically, all classes are found in Smalltalk)
+
+            idx := name lastIndexOf:$:.
+            idx ~~ 0 ifTrue:[
+                (name at:idx-1) == $: ifTrue:[
+                    nsName := name copyTo:(idx - 2).
+                    e := Smalltalk at:nsName asSymbol.
+                ]
+            ].
+        ].
+        environment := e.
     ].
     ^ environment
 
@@ -1073,16 +1082,16 @@
     |newPackage oldPackage|
 
     aSymbol == PackageId noProjectID ifTrue:[
-	newPackage := nil
+        newPackage := nil
     ] ifFalse:[
-	newPackage := aSymbol
+        newPackage := aSymbol
     ].
     package ~= newPackage ifTrue:[
-	oldPackage := package.
-	package := newPackage.
-
-	self changed:#package.
-	Smalltalk changed:#projectOrganization with:(Array with:self with:oldPackage).
+        oldPackage := package.
+        package := newPackage.
+
+        self changed:#package.
+        Smalltalk changed:#projectOrganization with:(Array with:self with:oldPackage).
     ].
 
     "Modified: / 09-08-2006 / 17:58:53 / fm"
@@ -1346,25 +1355,25 @@
 
     classes := self privateClasses.
     classes notEmpty ifTrue:[
-	classes := classes asOrderedCollection.
-	classes sort:[:a :b | a name < b name].
-
-	pivateClassesOf := IdentityDictionary new.
-	classes do:[:each | pivateClassesOf at:each put:(each allPrivateClasses)].
-
-	classes topologicalSort:[:a :b |
-	    "/ a must come before b iff:
-	    "/    b is a subclass of a
-	    "/    b has a private class which is a subclass of a
-
-	    |mustComeBefore pivateClassesOfB|
-	    mustComeBefore := b isSubclassOf:a.
-	    pivateClassesOfB := pivateClassesOf at:b.
-	    pivateClassesOfB do:[:eachClassInB |
-		mustComeBefore := mustComeBefore or:[eachClassInB isSubclassOf:a]
-	    ].
-	    mustComeBefore
-	].
+        classes := classes asOrderedCollection.
+        classes sort:[:a :b | a name < b name].
+
+        pivateClassesOf := IdentityDictionary new.
+        classes do:[:each | pivateClassesOf at:each put:(each allPrivateClasses)].
+
+        classes topologicalSort:[:a :b |
+            "/ a must come before b iff:
+            "/    b is a subclass of a
+            "/    b has a private class which is a subclass of a
+
+            |mustComeBefore pivateClassesOfB|
+            mustComeBefore := b isSubclassOf:a.
+            pivateClassesOfB := pivateClassesOf at:b.
+            pivateClassesOfB do:[:eachClassInB |
+                mustComeBefore := mustComeBefore or:[eachClassInB isSubclassOf:a]
+            ].
+            mustComeBefore
+        ].
     ].
     ^ classes.
 
@@ -1413,14 +1422,14 @@
 
     poolNames := self sharedPoolNames.
     (ns := self topNameSpace) notNil ifTrue:[
-	^ poolNames
-		collect:[:nm |
-		    |p|
-		    (p := ns at:nm asSymbol) notNil ifTrue:[
-			p name
-		    ] ifFalse:[
-			nm
-		    ]].
+        ^ poolNames
+                collect:[:nm |
+                    |p|
+                    (p := ns at:nm asSymbol) notNil ifTrue:[
+                        p name
+                    ] ifFalse:[
+                        nm
+                    ]].
     ].
     ^ poolNames
 
@@ -1724,15 +1733,79 @@
     "Modified: / 05-12-2006 / 22:04:26 / cg"
 !
 
+sourceCodeManagerFromBinaryRevision
+
+    "Returns the source code manager that should be used for
+     source code access based in class's binary revision.
+     If not binary revision is available, then configured source
+     code manager is returned. If source code management
+     is disabled or particular source code manager is not enabled,
+     return nil.
+
+     Source code manager for source access may differ from
+     configured source code manager:
+
+     - #sourceCodeManager returns the manager use has configured for
+       this class using preferences
+
+     - #sourceCodeManagerForSourceAccess is the manager used when asking
+       for class source code. It compares version_XXX methods with
+       class's binary revision and. When method_XXX matches the
+       binary revision string, XXX source code manager is returned,
+       as this class has been likely compiled from a source checked out
+       using returned source code manager
+
+    CAVEAT: Now, the code expects that the revision string is in
+    format '$revision ident$SCM'. It won't work for managers that
+    does not use dollar expansion. For, only CVS, SVN and Perforce
+    are used so this code should work
+    "
+
+
+
+
+    revision ifNil:[^self sourceCodeManager].
+
+    AbstractSourceCodeManager enabledManagers do:[:mgr|
+        (revision endsWith: mgr managerTypeNameShort) ifTrue:[
+            ^mgr
+        ]
+    ].
+
+    "binary revision is not nil and we haven't found source code manager.
+     This may happen when (i) given source code manager is not available
+     or (ii) source version methods are somehow corrupted.
+
+     Let's be strict about it for now and throw and error. More relaxed
+     version may simply return nil"
+
+"/    self error:'Cannot find source code manager for source access ' ,
+"/               '(manager yet not loaded or binary revision corrupted)'
+"/        mayProceed: true.
+
+    ^nil
+
+
+    "
+        Object sourceCodeManager
+        Object sourceCodeManagerForSourceAccess
+
+        JavaVM sourceCodeManager
+        JavaVM sourceCodeManagerForSourceAccess
+    "
+
+    "Created: / 06-10-2011 / 09:33:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 subclasses
     "return a collection of the direct subclasses of the receiver"
 
     "/ use cached information (avoid class hierarchy search), if possible
-    (subclasses isNil
+    (subclasses isNil 
     or:[ subclasses sequenceNumber ~= SubclassCacheSequenceNumber ]) ifTrue:[
-	self updateAllCachedSubclasses.
-	"subclasses may still be nil - obsolete classes may not be updated"
-	^ subclasses ? #().
+        self updateAllCachedSubclasses.
+        "subclasses may still be nil - obsolete classes may not be updated"
+        ^ subclasses ? #().
     ].
     ^ subclasses.
 
@@ -1799,6 +1872,7 @@
     "Created: / 18-07-2011 / 09:14:38 / cg"
 ! !
 
+
 !Class methodsFor:'adding & removing'!
 
 removeFromSystem
@@ -1895,14 +1969,14 @@
     "add a category change"
 
     UpdateChangeFileQuerySignal query ifTrue:[
-	self writingChangePerform:#addChangeRecordForChangeCategory:to: with:category.
+        self writingChangePerform:#addChangeRecordForChangeCategory:to: with:category.
     ].
 
     "this test allows a smalltalk without Projects/ChangeSets"
     Project notNil ifTrue:[
-	UpdateChangeListQuerySignal query ifTrue:[
-	    Project addClassDefinitionChangeFor:self
-	]
+        UpdateChangeListQuerySignal query ifTrue:[
+            Project addClassDefinitionChangeFor:self
+        ]
     ]
 !
 
@@ -2194,6 +2268,7 @@
     "Modified: / 18.3.1999 / 18:15:30 / stefan"
 ! !
 
+
 !Class methodsFor:'enumerating'!
 
 allPrivateClassesDo:aBlock
@@ -2233,6 +2308,7 @@
     self allPrivateClasses do:aBlock
 ! !
 
+
 !Class methodsFor:'fileIn interface'!
 
 primitiveDefinitions
@@ -2274,6 +2350,7 @@
     "Modified: 10.2.1996 / 12:47:28 / cg"
 ! !
 
+
 !Class methodsFor:'fileOut'!
 
 basicFileOutDefinitionOn:aStream withNameSpace:forceNameSpace
@@ -2601,9 +2678,9 @@
     self printClassNameOn:aStream.
     aStream nextPutAll:' comment:'.
     (comment := self comment) isNil ifTrue:[
-	s := ''''''
+        s := ''''''
     ] ifFalse:[
-	s := comment storeString
+        s := comment storeString
     ].
     aStream nextPutAllAsChunk:s.
     aStream nextPutChunkSeparator.
@@ -2715,24 +2792,24 @@
     |encoder any16Bit|
 
     any16Bit := self withAllPrivateClasses contains:[:cls |
-		 cls instAndClassMethods contains:
-		    [:m |
-			|src|
-
-			src := m source.
-			src notNil and:[src isWideString]
-		    ]].
+                 cls instAndClassMethods contains:
+                    [:m |
+                        |src|
+
+                        src := m source.
+                        src notNil and:[src isWideString]
+                    ]].
 
     any16Bit ifTrue:[
-	encoder := CharacterEncoder encoderForUTF8.
+        encoder := CharacterEncoder encoderForUTF8.
     ].
     ^ self
-	fileOutOn:aStream
-	withTimeStamp:stampIt
-	withInitialize:initIt
-	withDefinition:withDefinition
-	methodFilter:methodFilter
-	encoder:encoder
+        fileOutOn:aStream
+        withTimeStamp:stampIt
+        withInitialize:initIt
+        withDefinition:withDefinition
+        methodFilter:methodFilter
+        encoder:encoder
 
     "Modified: / 18-07-2011 / 09:17:17 / cg"
 !
@@ -2793,13 +2870,13 @@
      primitive functions - if any
     "
     (s := self primitiveFunctionsString) notNil ifTrue:[
-	aStream nextPutChunkSeparator.
-	self printClassNameOn:aStream.
-	aStream nextPutAll:' primitiveFunctions';
-		nextPutChunkSeparator;
-		cr.
-	aStream nextPutAll:s.
-	aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
+        aStream nextPutChunkSeparator.
+        self printClassNameOn:aStream.
+        aStream nextPutAll:' primitiveFunctions';
+                nextPutChunkSeparator;
+                cr.
+        aStream nextPutAll:s.
+        aStream nextPutChunkSeparator; space; nextPutChunkSeparator; cr; cr
     ].
 !
 
@@ -2816,12 +2893,13 @@
      primitive functions - if any
     "
     (s := self primitiveFunctionsString) notNil ifTrue:[
-	self fileOutPrimitiveFunctionsOn:aStream
+        self fileOutPrimitiveFunctionsOn:aStream
     ].
 
     "Modified: 8.1.1997 / 17:45:51 / cg"
 ! !
 
+
 !Class methodsFor:'fileOut-binary'!
 
 binaryFileOut
@@ -2921,6 +2999,7 @@
     "Created: / 29.12.1998 / 21:38:38 / cg"
 ! !
 
+
 !Class methodsFor:'fileOut-xml'!
 
 fileOutXML
@@ -3054,26 +3133,26 @@
     aStream nextPutAll:'  <inst-vars>'.
     varNames := self instVarNames.
     varNames size > 0 ifTrue:[
-	aStream cr.
-	varNames do:[:nm |
-	    aStream nextPutAll:'    <name>'.
-	    aStream nextPutAll:nm.
-	    aStream nextPutLine:'</name>'.
-	].
-	aStream nextPutAll:'  '.
+        aStream cr.
+        varNames do:[:nm |
+            aStream nextPutAll:'    <name>'.
+            aStream nextPutAll:nm.
+            aStream nextPutLine:'</name>'.
+        ].
+        aStream nextPutAll:'  '.
     ].
     aStream nextPutLine:'</inst-vars>'.
 
     aStream nextPutAll:'  <class-inst-vars>'.
     varNames := self class instVarNames.
     varNames size > 0 ifTrue:[
-	aStream cr.
-	varNames do:[:nm |
-	    aStream nextPutAll:'    <name>'.
-	    aStream nextPutAll:nm.
-	    aStream nextPutLine:'</name>'.
-	].
-	aStream nextPutAll:'  '.
+        aStream cr.
+        varNames do:[:nm |
+            aStream nextPutAll:'    <name>'.
+            aStream nextPutAll:nm.
+            aStream nextPutLine:'</name>'.
+        ].
+        aStream nextPutAll:'  '.
     ].
     aStream nextPutLine:'</class-inst-vars>'.
 
@@ -3088,14 +3167,14 @@
     aStream nextPutLine:'</class>'.
 
     self classVarNames do:[:nm |
-	aStream nextPutLine:'<static>'.
-	aStream nextPutAll:' <name>'.
-	aStream nextPutAll:nm.
-	aStream nextPutLine:'</name>'.
-	aStream nextPutAll:' <environment>'.
-	aStream nextPutAll:self name.
-	aStream nextPutLine:'</environment>'.
-	aStream nextPutLine:'</static>'.
+        aStream nextPutLine:'<static>'.
+        aStream nextPutAll:' <name>'.
+        aStream nextPutAll:nm.
+        aStream nextPutLine:'</name>'.
+        aStream nextPutAll:' <environment>'.
+        aStream nextPutAll:self name.
+        aStream nextPutLine:'</environment>'.
+        aStream nextPutLine:'</static>'.
     ].
 !
 
@@ -3410,6 +3489,7 @@
     aStream nextPutAll:self name
 ! !
 
+
 !Class methodsFor:'private-accessing'!
 
 attributes
@@ -3564,25 +3644,25 @@
 
     subclassesPerClass := Dictionary new.
     Smalltalk allClassesDo:[:each |
-	|cls superclass|
-
-	cls := each theNonMetaclass.
-	(superclass := each superclass) notNil ifTrue:[
-	    (subclassesPerClass at:superclass ifAbsentPut:makeNewSet) add:cls
-	].
-	subclassesPerClass at:cls ifAbsentPut:makeNewSet.
+        |cls superclass|
+
+        cls := each theNonMetaclass.
+        (superclass := each superclass) notNil ifTrue:[
+            (subclassesPerClass at:superclass ifAbsentPut:makeNewSet) add:cls
+        ].
+        subclassesPerClass at:cls ifAbsentPut:makeNewSet.
     ].
 
     SubclassCacheSequenceNumber isNil ifTrue:[
-	SubclassCacheSequenceNumber := 0.
+        SubclassCacheSequenceNumber := 0.
     ].
     seqNr := SubclassCacheSequenceNumber.
     subclassesPerClass keysAndValuesDo:[:cls :subclasses |
-	|coll|
-
-	coll := ArrayWithSequenceNumberValidation withAll:subclasses.
-	coll sequenceNumber:seqNr.
-	cls setSubclasses:coll.
+        |coll|
+
+        coll := ArrayWithSequenceNumberValidation withAll:subclasses.
+        coll sequenceNumber:seqNr.
+        cls setSubclasses:coll.
     ].
 
     "
@@ -3593,6 +3673,7 @@
     "Created: / 28-04-2010 / 08:47:20 / cg"
 ! !
 
+
 !Class methodsFor:'private-changes management'!
 
 addChangeRecordForChangeCategory:category to:aStream
@@ -3647,10 +3728,10 @@
 
     "append a class-remove-record to aStream"
 
-    aStream
-	nextPutAll:'Smalltalk removeClass:';
-	nextPutAll:oldClass name;
-	nextPutChunkSeparator.
+    aStream 
+        nextPutAll:'Smalltalk removeClass:';
+        nextPutAll:oldClass name;
+        nextPutChunkSeparator.
 !
 
 addChangeRecordForClassRename:oldName to:newName to:aStream
@@ -3658,13 +3739,13 @@
 
     "append a class-rename-record to aStream"
 
-    aStream
-	nextPutAll:'Smalltalk renameClass:';
-	nextPutAll:oldName;
-	nextPutAll:' to:''';
-	nextPutAll:newName;
-	nextPutAll:'''';
-	nextPutChunkSeparator.
+    aStream 
+        nextPutAll:'Smalltalk renameClass:';
+        nextPutAll:oldName;
+        nextPutAll:' to:''';
+        nextPutAll:newName;
+        nextPutAll:'''';
+        nextPutChunkSeparator.
 
     "Modified: / 01-06-2012 / 09:44:04 / cg"
 !
@@ -3705,6 +3786,7 @@
     "Modified: 9.11.1996 / 00:10:10 / cg"
 ! !
 
+
 !Class methodsFor:'queries'!
 
 canHaveExtensions
@@ -3826,15 +3908,15 @@
     aPackageID = clsPkg ifTrue:[^ false].
 
     self instAndClassMethodsDo:[:mthd |
-	mthd package = aPackageID ifTrue:[ ^ true].
+        mthd package = aPackageID ifTrue:[ ^ true].
     ].
     ^ false
 
     "
      Smalltalk allClasses
-	select:[:each | each hasExtensionsFrom:'stx:goodies/refactyBrowser']
+        select:[:each | each hasExtensionsFrom:'stx:goodies/refactyBrowser']
      Smalltalk allClasses
-	select:[:each | each hasExtensionsFrom:'stx:libboss']
+        select:[:each | each hasExtensionsFrom:'stx:libboss']
     "
 
     "Modified: / 06-03-2007 / 11:55:39 / cg"
@@ -3963,6 +4045,7 @@
     "
 ! !
 
+
 !Class methodsFor:'renaming'!
 
 makePrivateIn:newOwner
@@ -4090,6 +4173,7 @@
     "Modified: / 31.7.1998 / 15:21:34 / cg"
 ! !
 
+
 !Class methodsFor:'signature checking'!
 
 classinstSizeFromSignature:aSignature
@@ -4191,6 +4275,7 @@
     "Created: 1.4.1997 / 15:23:24 / stefan"
 ! !
 
+
 !Class methodsFor:'source management'!
 
 binaryRevision
@@ -4199,20 +4284,23 @@
      If a classes binary is up-to-date w.r.t. the source repository,
      the returned string is the same as the one returned by #revision."
 
-    |owner info c|
+    |owner manager info c|
 
     (owner := self owningClass) notNil ifTrue:[^ owner binaryRevision].
 
     revision notNil ifTrue:[
-	c := revision first.
-	c == $$ ifTrue:[
-	    info := Class revisionInfoFromString:revision.
-	    info isNil ifTrue:[^ '0'].
-	    ^ (info revision) ? '0'.
-	].
-	c isDigit ifFalse:[
-	    ^ '0'
-	].
+        c := revision first.
+        c == $$ ifTrue:[
+            manager := self sourceCodeManagerFromBinaryRevision.
+            manager notNil ifTrue:[
+                info := manager revisionInfoFromString:revision.
+            ].
+            info isNil ifTrue:[^ '0'].
+            ^ (info revision) ? '0'.
+        ].
+        c isDigit ifFalse:[
+            ^ '0'
+        ].
     ].
 
     ^ revision
@@ -4228,13 +4316,14 @@
      |classes|
 
      classes := Smalltalk allClasses
-		    select:[:cls | cls binaryRevision notNil and:[cls binaryRevision ~= cls revision]].
+                    select:[:cls | cls binaryRevision notNil and:[cls binaryRevision ~= cls revision]].
      SystemBrowser browseClasses:classes title:'classes which are not up-to-date'
     "
 
     "Created: / 07-12-1995 / 10:58:47 / cg"
     "Modified: / 01-04-1997 / 23:33:01 / stefan"
     "Modified: / 22-10-2008 / 20:37:05 / cg"
+    "Modified: / 23-01-2012 / 19:38:50 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 binaryRevisionString
@@ -4318,41 +4407,41 @@
     (owner := self owningClass) notNil ifTrue:[^ owner findVersionMethodOfManager:aSourceCodemanagerOrNil].
 
     tryVersionFromVersionMethod :=
-	[:versionMethodsName |
-	    |aVersionMethod val|
-
-	    aVersionMethod := meta compiledMethodAt:versionMethodsName.
-	    (aVersionMethod notNil and:[aVersionMethod isExecutable]) ifTrue:[
-		"/
-		"/ if it's a method returning the version string,
-		"/ that's the returned value
-		"/
-		val := cls perform:versionMethodsName.
-		val isString ifTrue:[^ aVersionMethod].
-	    ].
-	].
+        [:versionMethodsName |
+            |aVersionMethod val|
+
+            aVersionMethod := meta compiledMethodAt:versionMethodsName.
+            (aVersionMethod notNil and:[aVersionMethod isExecutable]) ifTrue:[
+                "/
+                "/ if it's a method returning the version string,
+                "/ that's the returned value
+                "/
+                val := cls perform:versionMethodsName.
+                val isString ifTrue:[^ aVersionMethod].
+            ].
+        ].
 
     meta := self theMetaclass.
     cls := self theNonMetaclass.
 
-    prefixOfVersionMethodSelector :=
-	AbstractSourceCodeManager notNil
-	    ifTrue: [AbstractSourceCodeManager prefixOfVersionMethodSelector ]
-	    ifFalse:[ 'version_' ].     "/ sigh - for standalone apps without libbasic3
+    prefixOfVersionMethodSelector := 
+        AbstractSourceCodeManager notNil 
+            ifTrue: [AbstractSourceCodeManager prefixOfVersionMethodSelector ]
+            ifFalse:[ 'version_' ].     "/ sigh - for standalone apps without libbasic3
 
     allVersionMethodNames := meta methodDictionary keys select:[:sel | sel startsWith:prefixOfVersionMethodSelector].
 
     aSourceCodemanagerOrNil notNil ifTrue:[
-	nameOfVersionMethodForManager := aSourceCodemanagerOrNil nameOfVersionMethodInClasses.
-	(allVersionMethodNames includes:nameOfVersionMethodForManager) ifTrue:[
-	    tryVersionFromVersionMethod value:nameOfVersionMethodForManager
-	].
-
-	"/ only trust the oldVersion method, iff there is no other scv-version
-	"/ (i.e. do not misuse an svn-checked-in #version as a version_cvs)
-	(allVersionMethodNames copyWithout:nameOfVersionMethodForManager) notEmpty ifTrue:[
-	    ^ nil
-	].
+        nameOfVersionMethodForManager := aSourceCodemanagerOrNil nameOfVersionMethodInClasses.
+        (allVersionMethodNames includes:nameOfVersionMethodForManager) ifTrue:[
+            tryVersionFromVersionMethod value:nameOfVersionMethodForManager
+        ].
+
+        "/ only trust the oldVersion method, iff there is no other scv-version
+        "/ (i.e. do not misuse an svn-checked-in #version as a version_cvs)
+        (allVersionMethodNames copyWithout:nameOfVersionMethodForManager) notEmpty ifTrue:[
+            ^ nil
+        ].
     ].
 
     nameOfOldVersionMethod := self nameOfOldVersionMethod.
@@ -4362,7 +4451,7 @@
 
     "
      Smalltalk allClassesDo:[:cls |
-	Transcript show:cls name; show:' -> '; showCR:cls findVersionMethod
+        Transcript show:cls name; show:' -> '; showCR:cls findVersionMethod
      ].
 
      Number findVersionMethod
@@ -4537,11 +4626,11 @@
      (this is done for backward compatibility,)
 
      For example:
-	'....(libbasic)'                         -> module: stx directory: libbasic library: libbasic
-	'....(stx:libbasic)'                     -> module: stx directory: libbasic library: libbasic
-	'....(stx:foo:libbfoo)'                  -> module: stx directory: foo library: libfoo
-	'....(aeg:libIECInterface)'              -> module: aeg directory: libIECInterface library:libIECInterface
-	'....(stx:goodies/persistency:libdbase)' -> module: stx directory: goodies/persistency library:libdbase
+        '....(libbasic)'                         -> module: stx directory: libbasic library: libbasic
+        '....(stx:libbasic)'                     -> module: stx directory: libbasic library: libbasic
+        '....(stx:foo:libbfoo)'                  -> module: stx directory: foo library: libfoo
+        '....(aeg:libIECInterface)'              -> module: aeg directory: libIECInterface library:libIECInterface
+        '....(stx:goodies/persistency:libdbase)' -> module: stx directory: goodies/persistency library:libdbase
 
      The way how the sourceCodeManager uses this to find the source location
      depends on the scheme used. For CVS, the module is taken as the -d arg,
@@ -4549,7 +4638,7 @@
      Other schemes may do things differently - these are not yet specified.
 
      Caveat:
-	Encoding this info in the package string seems somewhat kludgy.
+        Encoding this info in the package string seems somewhat kludgy.
     "
 
     |owner sourceInfo packageString idx1 idx2
@@ -4563,12 +4652,12 @@
     packageString := package asString.
     idx1 := packageString lastIndexOf:$(.
     idx1 ~~ 0 ifTrue:[
-	idx2 := packageString indexOf:$) startingAt:idx1+1.
-	idx2 ~~ 0 ifTrue:[
-	    sourceInfo := packageString copyFrom:idx1 + 1 to:idx2 - 1
-	]
+        idx2 := packageString indexOf:$) startingAt:idx1+1.
+        idx2 ~~ 0 ifTrue:[
+            sourceInfo := packageString copyFrom:idx1 + 1 to:idx2 - 1
+        ]
     ] ifFalse:[
-	sourceInfo := packageString
+        sourceInfo := packageString
     ].
 
     sourceInfo isNil ifTrue:[^ nil].
@@ -4576,76 +4665,76 @@
     components notEmpty ifTrue:[
 "/        moduleString := 'stx'.
 "/        directoryString := libraryString := ''.
-	^ nil
+        ^ nil
     ].
 
     component1 := components at:1.
     components size == 1 ifTrue:[
-	"/ a single name given - the module becomes 'stx' or
-	"/ the very first directory component (if such a module exists).
-	"/ If the component includes slashes, its the directory
-	"/ otherwise the library.
-	"/
-	dirComponents := Filename components:component1.
-	(dirComponents size > 1
-	and:[(mgr := self sourceCodeManager) notNil
-	and:[mgr checkForExistingModule:dirComponents first]]) ifTrue:[
-	    moduleString := dirComponents first.
-	    directoryString := libraryString := (Filename fromComponents:(dirComponents copyFrom:2)) asString.
-	] ifFalse:[
-	    "/ non-existing; assume directory under the stx package.
-	    moduleString := 'stx'.
-	    (component1 startsWith:'stx/') ifTrue:[
-		component1 := component1 copyFrom:5
-	    ].
-	    directoryString := libraryString := component1.
-	].
-
-	(libraryString includes:$/) ifTrue:[
-	    libraryString := libraryString asFilename baseName
-	]
+        "/ a single name given - the module becomes 'stx' or
+        "/ the very first directory component (if such a module exists).
+        "/ If the component includes slashes, its the directory
+        "/ otherwise the library.
+        "/
+        dirComponents := Filename components:component1.
+        (dirComponents size > 1
+        and:[(mgr := self sourceCodeManager) notNil
+        and:[mgr checkForExistingModule:dirComponents first]]) ifTrue:[
+            moduleString := dirComponents first.
+            directoryString := libraryString := (Filename fromComponents:(dirComponents copyFrom:2)) asString.
+        ] ifFalse:[
+            "/ non-existing; assume directory under the stx package.
+            moduleString := 'stx'.
+            (component1 startsWith:'stx/') ifTrue:[
+                component1 := component1 copyFrom:5
+            ].
+            directoryString := libraryString := component1.
+        ].
+
+        (libraryString includes:$/) ifTrue:[
+            libraryString := libraryString asFilename baseName
+        ]
     ] ifFalse:[
-	moduleString := component1.
-	component2 := components at:2.
-	directoryString := component2.
-	components size == 2 ifTrue:[
-	    "/ two components - assume its the module and the directory;
-	    "/ the library is assumed to be named after the directory
-	    "/ except, if slashes are in the name; then the libraryname
-	    "/ is the last component.
-	    "/
-	    libraryString := component2.
-	    (libraryString includes:$/) ifTrue:[
-		libraryString := libraryString asFilename baseName
-	    ]
-	] ifFalse:[
-	    "/ all components given
-	    libraryString := components at:3.
-	]
+        moduleString := component1.
+        component2 := components at:2.
+        directoryString := component2.
+        components size == 2 ifTrue:[
+            "/ two components - assume its the module and the directory;
+            "/ the library is assumed to be named after the directory
+            "/ except, if slashes are in the name; then the libraryname
+            "/ is the last component.
+            "/
+            libraryString := component2.
+            (libraryString includes:$/) ifTrue:[
+                libraryString := libraryString asFilename baseName
+            ]
+        ] ifFalse:[
+            "/ all components given
+            libraryString := components at:3.
+        ]
     ].
 
     libraryString isEmpty ifTrue:[
-	directoryString notEmpty ifTrue:[
-	    libraryString := directoryString asFilename baseName
-	].
-	libraryString isEmpty ifTrue:[
-	    "/ lets extract the library from the liblist file ...
-	    libraryString := Smalltalk libraryFileNameOfClass:self.
-	    libraryString isNil ifTrue:[^ nil].
-	]
+        directoryString notEmpty ifTrue:[
+            libraryString := directoryString asFilename baseName
+        ].
+        libraryString isEmpty ifTrue:[
+            "/ lets extract the library from the liblist file ...
+            libraryString := Smalltalk libraryFileNameOfClass:self.
+            libraryString isNil ifTrue:[^ nil].
+        ]
     ].
 
     moduleString isEmpty ifTrue:[
-	moduleString := 'stx'.
+        moduleString := 'stx'.
     ].
     directoryString isEmpty ifTrue:[
-	directoryString := libraryString.
+        directoryString := libraryString.
     ].
 
     ^ IdentityDictionary
-	with:(#module->moduleString)
-	with:(#directory->directoryString)
-	with:(#library->libraryString)
+        with:(#module->moduleString)
+        with:(#directory->directoryString)
+        with:(#library->libraryString)
 
     "
      Object packageSourceCodeInfo
@@ -4764,7 +4853,7 @@
 	repositoryPath - the classes source container
     "
 
-    ^ self revisionInfoOfManager:self sourceCodeManager
+    ^ self revisionInfoOfManager:self sourceCodeManagerFromBinaryRevision
 
     "
      Object revisionString
@@ -5017,100 +5106,116 @@
     "/ or TryLocalSourceFirst is true,
     "/ look in standard places first
     "/
-    ((sourceCodeManager := self sourceCodeManager) isNil
-    or:[TryLocalSourceFirst == true]) ifTrue:[
-	sourceStream := self localSourceStreamFor:source.
+    "JV@2011-12-08: 
+        (i) first check TryLocalSourceFirst, this avoids useless call to
+            #sourceCodeManagerFromBinaryRevision when TryLocalSourceFirst is
+            set (for whatever reason)
+        (ii) do NOT ask source code manager during system startup - source code
+            managers are not configured anyway!! Also, avoids hangups during
+            startup when CVSROOT is set but server is unreacheable.
+    CAVEAT: When somebody modifies the code after compilation and methods
+        are recompiled during startup (for whatever reason), a bad code may
+        used, compilation may fail. However, it may happen anyway as SCM's
+        are not yet configured so the system may use wrong one. Moreover,
+        the source from which the class is compiled may not be the one in
+        repository. I (JV) think this is a good, less confusing compromise.
+    "
+    (TryLocalSourceFirst == true 
+        or:[Smalltalk isInitialized not
+            or: [(sourceCodeManager := self sourceCodeManagerFromBinaryRevision) isNil]])
+                ifTrue:[
+        sourceStream := self localSourceStreamFor:source.
+                ].
+
+    sourceStream isNil ifTrue:[
+        "/ mhmh - still no source file.
+        "/ If there is a SourceCodeManager, ask it to aquire the
+        "/ the source for my class, and return an open stream on it.
+        "/ if that one does not know about the source, look in
+        "/ standard places
+
+        sourceCodeManager notNil ifTrue:[
+            classFilename ~= source ifTrue:[
+                package notNil ifTrue:[
+                    sep := package indexOfAny:'/\:'.
+                    sep ~~ 0 ifTrue:[
+                        mod := package copyTo:sep - 1.
+                        dir := package copyFrom:sep + 1.
+                        sourceStream := sourceCodeManager streamForClass:nil fileName:source revision:(self binaryRevision) directory:dir module:mod cache:true.
+                    ]
+                ].
+            ].
+            sourceStream isNil ifTrue:[
+                classFilename isNil ifTrue:[
+                    guessedFileName := (Smalltalk fileNameForClass:self) , '.st'.
+                ].
+                source asFilename baseName = (classFilename ? guessedFileName) asFilename baseName ifTrue:[
+                    sourceStream := sourceCodeManager getSourceStreamFor:self.
+                ]
+            ].
+            sourceStream notNil ifTrue:[
+                (self validateSourceStream:sourceStream) ifFalse:[
+                    ('Class [info]: repositories source for "%1" is invalid.' bindWith:self theNonMetaclass name) errorPrintCR.
+                    sourceStream close.
+                    sourceStream := nil
+                ] ifTrue:[
+                    validated := true.
+                ].
+            ].
+        ]
     ].
 
     sourceStream isNil ifTrue:[
-	"/ mhmh - still no source file.
-	"/ If there is a SourceCodeManager, ask it to aquire the
-	"/ the source for my class, and return an open stream on it.
-	"/ if that one does not know about the source, look in
-	"/ standard places
-
-	sourceCodeManager notNil ifTrue:[
-	    classFilename ~= source ifTrue:[
-		package notNil ifTrue:[
-		    sep := package indexOfAny:'/\:'.
-		    sep ~~ 0 ifTrue:[
-			mod := package copyTo:sep - 1.
-			dir := package copyFrom:sep + 1.
-			sourceStream := sourceCodeManager streamForClass:nil fileName:source revision:(self binaryRevision) directory:dir module:mod cache:true.
-		    ]
-		].
-	    ].
-	    sourceStream isNil ifTrue:[
-		classFilename isNil ifTrue:[
-		    guessedFileName := (Smalltalk fileNameForClass:self) , '.st'.
-		].
-		source asFilename baseName = (classFilename ? guessedFileName) asFilename baseName ifTrue:[
-		    sourceStream := sourceCodeManager getSourceStreamFor:self.
-		]
-	    ].
-	    sourceStream notNil ifTrue:[
-		(self validateSourceStream:sourceStream) ifFalse:[
-		    ('Class [info]: repositories source for "%1" is invalid.' bindWith:self theNonMetaclass name) errorPrintCR.
-		    sourceStream close.
-		    sourceStream := nil
-		] ifTrue:[
-		    validated := true.
-		].
-	    ].
-	]
-    ].
-
-    sourceStream isNil ifTrue:[
-	"/
-	"/ hard case - there is no source file for this class
-	"/ (in the source-dir-path).
-	"/
-
-	"/
-	"/ look if my binary is from a dynamically loaded module,
-	"/ and, if so, look in the modules directory for the
-	"/ source file.
-	"/
-	ObjectFileLoader notNil ifTrue:[
-	    ObjectFileLoader loadedObjectHandlesDo:[:h |
-		|f classes|
-
-		sourceStream isNil ifTrue:[
-		    (classes := h classes) notEmptyOrNil ifTrue:[
-			(classes includes:self) ifTrue:[
-			    f := h pathName.
-			    f := f asFilename directory.
-			    f := f construct:source.
-			    f exists ifTrue:[
-				sourceStream := f readStreamOrNil.
-			    ].
-			].
-		    ].
-		]
-	    ].
-	].
+        "/
+        "/ hard case - there is no source file for this class
+        "/ (in the source-dir-path).
+        "/
+
+        "/
+        "/ look if my binary is from a dynamically loaded module,
+        "/ and, if so, look in the modules directory for the
+        "/ source file.
+        "/
+        ObjectFileLoader notNil ifTrue:[
+            ObjectFileLoader loadedObjectHandlesDo:[:h |
+                |f classes|
+
+                sourceStream isNil ifTrue:[
+                    (classes := h classes) notEmptyOrNil ifTrue:[
+                        (classes includes:self) ifTrue:[
+                            f := h pathName.
+                            f := f asFilename directory.
+                            f := f construct:source.
+                            f exists ifTrue:[
+                                sourceStream := f readStreamOrNil.
+                            ].
+                        ].
+                    ].
+                ]
+            ].
+        ].
     ].
 
     "/
     "/ try along sourcePath
     "/
     sourceStream isNil ifTrue:[
-	sourceStream := self localSourceStreamFor:source.
+        sourceStream := self localSourceStreamFor:source.
     ].
 
     "/
     "/ final chance: try current directory
     "/
     sourceStream isNil ifTrue:[
-	sourceStream := source asFilename readStreamOrNil.
+        sourceStream := source asFilename readStreamOrNil.
     ].
 
     (sourceStream notNil and:[validated not]) ifTrue:[
-	(self validateSourceStream:sourceStream) ifFalse:[
-	    ('Class [warning]: source for "%1" is invalid or stripped. Take care.' bindWith:self theNonMetaclass name) errorPrintCR.
-	    sourceStream close.
-	    sourceStream := nil
-	].
+        (self validateSourceStream:sourceStream) ifFalse:[
+            ('Class [warning]: source for "%1" is invalid or stripped. Take care.' bindWith:self theNonMetaclass name) errorPrintCR.
+            sourceStream close.
+            sourceStream := nil
+        ].
     ].
 "/    (sourceStream notNil and:[sourceStream isFileStream]) ifTrue:[
 "/        guessedFileName notNil ifTrue:[
@@ -5125,9 +5230,10 @@
      Autoload sourceStream
     "
 
-    "Created: / 10.11.1995 / 21:05:13 / cg"
-    "Modified: / 22.4.1998 / 19:20:50 / ca"
-    "Modified: / 5.11.2001 / 16:36:30 / cg"
+    "Created: / 10-11-1995 / 21:05:13 / cg"
+    "Modified: / 22-04-1998 / 19:20:50 / ca"
+    "Modified: / 05-11-2001 / 16:36:30 / cg"
+    "Modified: / 08-12-2011 / 19:16:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 updateVersionMethodFor:newRevisionString
@@ -5250,6 +5356,7 @@
     "Created: / 16-08-2009 / 12:57:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
 
+
 !Class::ArrayWithSequenceNumberValidation methodsFor:'accessing'!
 
 sequenceNumber
@@ -5260,6 +5367,7 @@
     sequenceNumber := something.
 ! !
 
+
 !Class::ArrayWithSequenceNumberValidation methodsFor:'checking'!
 
 checkIfValidFor:aSequenceNumber
@@ -5268,6 +5376,7 @@
     "Created: / 06-12-2011 / 16:01:16 / cg"
 ! !
 
+
 !Class::ClassAttributes class methodsFor:'documentation'!
 
 documentation
@@ -5279,6 +5388,7 @@
 "
 ! !
 
+
 !Class::ClassAttributes methodsFor:'accessing'!
 
 fGuid
@@ -5367,6 +5477,7 @@
     "Created: / 23-09-2011 / 10:23:26 / cg"
 ! !
 
+
 !Class::ClassAttributes methodsFor:'conversion'!
 
 fromSTCPrimitiveArray:anArray
@@ -5382,6 +5493,7 @@
     ].
 ! !
 
+
 !Class::SimulatedClassPool class methodsFor:'documentation'!
 
 documentation
@@ -5415,6 +5527,7 @@
 
 ! !
 
+
 !Class::SimulatedClassPool methodsFor:'accessing'!
 
 associationAt:aName
@@ -5494,12 +5607,14 @@
     ].
 ! !
 
+
 !Class::SimulatedClassPool methodsFor:'accessing-private'!
 
 setClass:aClass
     class := aClass
 ! !
 
+
 !Class::SimulatedClassPool::SimulatedVariableBinding class methodsFor:'documentation'!
 
 documentation
@@ -5508,6 +5623,7 @@
 "
 ! !
 
+
 !Class::SimulatedClassPool::SimulatedVariableBinding methodsFor:'queries'!
 
 isVariableBinding
@@ -5516,6 +5632,7 @@
     "Created: / 4.2.2000 / 00:27:20 / cg"
 ! !
 
+
 !Class class methodsFor:'documentation'!
 
 version
--- a/Context.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Context.st	Thu Mar 28 12:21:50 2013 +0000
@@ -2230,7 +2230,7 @@
         ].
 
         method notNil ifTrue:[
-            ^ method methodArgAndVarNames.
+            ^ method methodArgAndVarNamesInContext: self.
         ].
         ^ #()
     ].
@@ -2271,6 +2271,8 @@
     ].
 
     ^ #()
+
+    "Modified: / 18-12-2012 / 18:18:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 canResume
--- a/ContextError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ContextError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#ContextError
@@ -44,5 +43,12 @@
 !ContextError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ContextError.st,v 1.4 2003-08-29 19:21:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ContextError.st,v 1.4 2003/08/29 19:21:35 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: ContextError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/Continuation.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Continuation.st	Thu Mar 28 12:21:50 2013 +0000
@@ -186,5 +186,12 @@
 !Continuation class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Continuation.st,v 1.15 2008-11-03 11:20:32 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Continuation.st,v 1.15 2008/11/03 11:20:32 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: Continuation.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/ControlInterrupt.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ControlInterrupt.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 GenericException subclass:#ControlInterrupt
@@ -52,5 +51,12 @@
 !ControlInterrupt class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ControlInterrupt.st,v 1.7 2003-10-07 13:25:13 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ControlInterrupt.st,v 1.7 2003/10/07 13:25:13 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: ControlInterrupt.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/ControlRequest.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ControlRequest.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Exception subclass:#ControlRequest
@@ -44,5 +43,12 @@
 !ControlRequest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ControlRequest.st,v 1.4 2003-10-07 13:25:12 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ControlRequest.st,v 1.4 2003/10/07 13:25:12 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: ControlRequest.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/ConversionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ConversionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#ConversionError
@@ -51,7 +50,14 @@
 !ConversionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ConversionError.st,v 1.6 2004-08-22 17:47:16 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ConversionError.st,v 1.6 2004/08/22 17:47:16 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: ConversionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 ConversionError initialize!
+
+
+
--- a/DateConversionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/DateConversionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -43,7 +43,14 @@
 !DateConversionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/DateConversionError.st,v 1.1 2008-08-06 09:23:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/DateConversionError.st,v 1.1 2008/08/06 09:23:17 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: DateConversionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 DateConversionError initialize!
+
+
+
--- a/DecodingError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/DecodingError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 CharacterEncoderError subclass:#DecodingError
@@ -38,5 +37,12 @@
 !DecodingError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/DecodingError.st,v 1.2 2004-03-09 21:59:09 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/DecodingError.st,v 1.2 2004/03/09 21:59:09 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: DecodingError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/DeepCopyError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/DeepCopyError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#DeepCopyError
@@ -50,7 +49,14 @@
 !DeepCopyError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/DeepCopyError.st,v 1.1 2004-04-23 11:15:48 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/DeepCopyError.st,v 1.1 2004/04/23 11:15:48 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: DeepCopyError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 DeepCopyError initialize!
+
+
+
--- a/DomainError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/DomainError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ArithmeticError subclass:#DomainError
@@ -55,7 +54,14 @@
 !DomainError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/DomainError.st,v 1.4 2003-08-29 19:14:53 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/DomainError.st,v 1.4 2003/08/29 19:14:53 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: DomainError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 DomainError initialize!
+
+
+
--- a/ElementBoundsError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ElementBoundsError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Error subclass:#ElementBoundsError
@@ -54,7 +53,14 @@
 !ElementBoundsError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ElementBoundsError.st,v 1.1 2004-04-23 11:16:20 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ElementBoundsError.st,v 1.1 2004/04/23 11:16:20 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: ElementBoundsError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 ElementBoundsError initialize!
+
+
+
--- a/EncodedStream.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/EncodedStream.st	Thu Mar 28 12:21:50 2013 +0000
@@ -59,8 +59,12 @@
         decoder := CharacterEncoder nullEncoderInstance.
     ].
     decodedStream := self stream:aStream encoder:decoder.
-    decodedStream skipEncodingChunk.
+    "JV@2012-03-27: NO, DO NOT CHANGE POSITION!! Caller might be interested
+                    in all data!!!!!!"
+    "/decodedStream skipEncodingChunk.
     ^ decodedStream
+
+    "Modified: / 27-03-2013 / 17:08:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
 !EncodedStream methodsFor:'accessing'!
@@ -105,6 +109,163 @@
     stream := something.
 ! !
 
+!EncodedStream methodsFor:'private fileIn'!
+
+basicFileInNotifying:someone passChunk:passChunk
+    "central method to file in from the receiver, i.e. read chunks and evaluate them -
+     return the value of the last chunk.
+     Someone (which is usually some codeView) is notified of errors."
+
+    |lastValue pkg nameSpace usedNameSpaces
+     packageQuerySignal nameSpaceQuerySignal usedNameSpaceQuerySignal
+     changeDefaultApplicationNotificationSignal
+     defaultApplicationQuerySignal defaultApplication
+     confirmationQuerySignal handledSignals passedSignals askSomeoneForPackage outerContext askForVariableTypeOfUndeclaredQuery|
+
+    self skipSeparators.
+    lastValue := self peek.
+    lastValue == $< ifTrue:[
+        "/ assume, it's an xml file
+        ^ self fileInXMLNotifying:someone passChunk:passChunk.
+    ].
+    lastValue == $# ifTrue:[
+        "assume unix interpreter name:
+         '#!!stx -e' or something like this"
+        self nextPeek == $!! ifTrue:[
+            "skip the unix command line"
+            self nextLine
+        ] ifFalse:[
+             self error:'Invalid chunk start'
+        ]
+    ].
+
+    Smalltalk::Compiler isNil ifTrue:[
+        self isFileStream ifTrue:[
+            Transcript show:('[' , self pathName , '] ').
+        ].
+        Transcript showCR:'cannot fileIn (no compiler).'.
+        ^ nil.
+    ].
+
+    "/ support for V'Age applications
+    defaultApplicationQuerySignal := Class defaultApplicationQuerySignal.
+    changeDefaultApplicationNotificationSignal := Class changeDefaultApplicationNotificationSignal.
+
+    "/ support for ST/X's nameSpaces & packages
+    packageQuerySignal := Class packageQuerySignal.
+    nameSpaceQuerySignal := Class nameSpaceQuerySignal.
+    usedNameSpaceQuerySignal := Class usedNameSpaceQuerySignal.
+
+    (someone respondsTo:#packageToInstall) ifTrue:[
+        pkg := someone packageToInstall.
+        askSomeoneForPackage := true.
+    ] ifFalse:[
+        pkg := packageQuerySignal query.
+        askSomeoneForPackage := false.
+    ].
+    (someone respondsTo:#currentNameSpace) ifTrue:[
+        nameSpace := someone currentNameSpace
+    ] ifFalse:[
+        nameSpace := nameSpaceQuerySignal query.
+    ].
+    (someone respondsTo:#usedNameSpaces) ifTrue:[
+        usedNameSpaces := someone usedNameSpaces
+    ] ifFalse:[
+        usedNameSpaces := usedNameSpaceQuerySignal query.
+    ].
+    (someone respondsTo:#defaultApplication) ifTrue:[
+        defaultApplication := someone defaultApplication
+    ] ifFalse:[
+        defaultApplication := defaultApplicationQuerySignal query.
+    ].
+
+    confirmationQuerySignal := Metaclass confirmationQuerySignal.
+
+    handledSignals := SignalSet new.
+    passedSignals := IdentitySet new.
+
+    handledSignals add:changeDefaultApplicationNotificationSignal.
+    passedSignals add:changeDefaultApplicationNotificationSignal.
+    handledSignals add:defaultApplicationQuerySignal.
+    passedSignals add:defaultApplicationQuerySignal.
+
+    handledSignals add:packageQuerySignal.
+    handledSignals add:usedNameSpaceQuerySignal.
+    handledSignals add:nameSpaceQuerySignal.
+    handledSignals add:confirmationQuerySignal.
+    passedSignals add:confirmationQuerySignal.
+    Parser notNil ifTrue:[
+        "only if libcomp is present"
+        "Also catch a 'Parser askForVariableTypeOfUndeclaredQuery' and proceed with nil. 
+         Imagine somebody has autodefine workspace variables on and then 
+         evaluate Smalltalk loadPackage:'xyz' that loads code from source (using file-in), 
+         certainly we don't want to compile workspace variable access for every
+         not-yet-loaded class in some namespace. 
+         This is demonstrated by Regression::CompilerTests2>>test_01 
+         and this change actually fixes this test."
+        askForVariableTypeOfUndeclaredQuery := Parser askForVariableTypeOfUndeclaredQuery.
+        handledSignals add:askForVariableTypeOfUndeclaredQuery.
+    ].
+
+
+    outerContext := thisContext.
+
+    handledSignals handle:[:ex |
+        |sig|
+
+        sig := ex signal.
+        ((passedSignals includes:sig) and:[sig isHandledIn:outerContext]) ifTrue:[
+            ex reject
+        ].
+        
+        sig == changeDefaultApplicationNotificationSignal ifTrue:[
+            "/ invoked via #becomeDefault to set the defaultApp and the package.
+            "/ (only when filing in V'Age code)
+            defaultApplication := ex parameter.
+            pkg := defaultApplication name asSymbol.
+            ex proceedWith:nil
+        ].
+        sig == defaultApplicationQuerySignal ifTrue:[
+            "/ query for the application to add classes & methods into
+            "/ (only when filing in V'Age code)
+            ex proceedWith:defaultApplication
+        ].
+        sig == packageQuerySignal ifTrue:[
+            "answer the package to use for classes & methods"
+            askSomeoneForPackage ifTrue:[
+                ex proceedWith:someone packageToInstall
+            ] ifFalse:[
+                ex proceedWith:pkg
+            ]
+        ].
+        sig == usedNameSpaceQuerySignal ifTrue:[
+            "answer the nameSpaces to be searched when encountering globals"
+            ex proceedWith:usedNameSpaces
+        ].
+        sig == nameSpaceQuerySignal ifTrue:[
+            "answer the nameSpace to install new classes in"
+            ex proceedWith:nameSpace
+        ].
+        sig == confirmationQuerySignal ifTrue:[
+            "don't pop up dialogs"
+            ex proceedWith:false
+        ].
+        sig == askForVariableTypeOfUndeclaredQuery ifTrue:[
+           "no autodefined variables or so"
+            ex proceedWith:nil.
+        ].
+    ] do:[
+        [self atEnd] whileFalse:[
+            lastValue := self fileInNextChunkNotifying:someone passChunk:passChunk
+        ]
+    ].
+    ^ lastValue
+
+    "Modified: / 10.9.1999 / 16:54:01 / stefan"
+    "Modified: / 16.11.2001 / 16:21:28 / cg"
+    "Modified: / 18-03-2013 / 17:45:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+! !
+
 !EncodedStream methodsFor:'stream protocol'!
 
 atEnd
@@ -298,6 +459,12 @@
     ^ '$Header: /cvs/stx/stx/libbasic/EncodedStream.st,v 1.26 2012-08-31 18:01:03 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '§ Id: EncodedStream.st 10643 2011-06-08 21:53:07Z vranyj1  §'
 ! !
+
--- a/EncodingError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/EncodingError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 CharacterEncoderError subclass:#EncodingError
@@ -38,5 +37,12 @@
 !EncodingError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/EncodingError.st,v 1.2 2004-03-09 21:57:20 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/EncodingError.st,v 1.2 2004/03/09 21:57:20 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: EncodingError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/EndOfStreamError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/EndOfStreamError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#EndOfStreamError
@@ -64,7 +63,14 @@
 !EndOfStreamError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/EndOfStreamError.st,v 1.1 2005-11-16 08:45:55 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/EndOfStreamError.st,v 1.1 2005/11/16 08:45:55 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: EndOfStreamError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 EndOfStreamError initialize!
+
+
+
--- a/EndOfStreamNotification.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/EndOfStreamNotification.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Notification subclass:#EndOfStreamNotification
@@ -58,5 +57,12 @@
 !EndOfStreamNotification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/EndOfStreamNotification.st,v 1.3 2005-11-16 08:44:41 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/EndOfStreamNotification.st,v 1.3 2005/11/16 08:44:41 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: EndOfStreamNotification.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/Exception.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Exception.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 GenericException subclass:#Exception
@@ -62,6 +61,13 @@
 !Exception class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.82 2003-10-07 13:25:24 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Exception.st,v 1.82 2003/10/07 13:25:24 stefan Exp $'
+
+!
 
+version_SVN
+    ^ '$Id: Exception.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/ExceptionHandlerSet.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ExceptionHandlerSet.st	Thu Mar 28 12:21:50 2013 +0000
@@ -325,5 +325,12 @@
 !ExceptionHandlerSet class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ExceptionHandlerSet.st,v 1.17 2009-03-17 16:21:46 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ExceptionHandlerSet.st,v 1.17 2009/03/17 16:21:46 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: ExceptionHandlerSet.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/ExecutionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ExecutionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#ExecutionError
@@ -50,7 +49,14 @@
 !ExecutionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ExecutionError.st,v 1.4 2003-09-05 10:26:58 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ExecutionError.st,v 1.4 2003/09/05 10:26:58 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: ExecutionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 ExecutionError initialize!
+
+
+
--- a/ExternalStructure.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ExternalStructure.st	Thu Mar 28 12:21:50 2013 +0000
@@ -66,6 +66,7 @@
 "
 ! !
 
+
 !ExternalStructure class methodsFor:'instance creation'!
 
 fromExternalAddress:anExternalAddress
@@ -107,6 +108,7 @@
     ^ super unprotectedNew:(self sizeof)
 ! !
 
+
 !ExternalStructure class methodsFor:'queries'!
 
 cType
@@ -122,12 +124,14 @@
     self subclassResponsibility
 ! !
 
+
 !ExternalStructure methodsFor:'private'!
 
 fromExternalAddress:anExternalAddress
     self setAddress:(anExternalAddress address) size:(anExternalAddress size).
 ! !
 
+
 !ExternalStructure class methodsFor:'documentation'!
 
 version
@@ -136,5 +140,9 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic/ExternalStructure.st,v 1.5 2013-01-28 18:04:13 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: ExternalStructure.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
--- a/Geometric.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Geometric.st	Thu Mar 28 12:21:50 2013 +0000
@@ -525,7 +525,14 @@
 !Geometric class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Geometric.st,v 1.31 2009-06-06 10:12:25 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Geometric.st,v 1.31 2009/06/06 10:12:25 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: Geometric.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 Geometric initialize!
+
+
+
--- a/HaltInterrupt.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/HaltInterrupt.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ControlInterrupt subclass:#HaltInterrupt
@@ -45,5 +44,12 @@
 !HaltInterrupt class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/HaltInterrupt.st,v 1.3 2003-08-29 19:18:06 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/HaltInterrupt.st,v 1.3 2003/08/29 19:18:06 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: HaltInterrupt.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/HandleRegistry.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/HandleRegistry.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Registry subclass:#HandleRegistry
@@ -73,5 +72,12 @@
 !HandleRegistry class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/HandleRegistry.st,v 1.9 2002-03-04 19:15:09 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/HandleRegistry.st,v 1.9 2002/03/04 19:15:09 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: HandleRegistry.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/IdentityDictionary.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/IdentityDictionary.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Dictionary subclass:#IdentityDictionary
@@ -163,6 +162,7 @@
     "Created: 19.3.1997 / 15:03:36 / cg"
 ! !
 
+
 !IdentityDictionary methodsFor:'testing'!
 
 includesValue:aValue
@@ -191,5 +191,12 @@
 !IdentityDictionary class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/IdentityDictionary.st,v 1.30 2002-11-29 11:08:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/IdentityDictionary.st,v 1.30 2002/11/29 11:08:54 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: IdentityDictionary.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/ImaginaryResultError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ImaginaryResultError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -55,7 +55,10 @@
 !ImaginaryResultError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ImaginaryResultError.st,v 1.2 2003-08-29 19:15:11 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ImaginaryResultError.st,v 1.2 2003/08/29 19:15:11 cg Exp $'
 ! !
 
 ImaginaryResultError initialize!
+
+
+
--- a/IncompleteNextCountError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/IncompleteNextCountError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#IncompleteNextCountError
@@ -64,7 +63,14 @@
 !IncompleteNextCountError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/IncompleteNextCountError.st,v 1.2 2003-08-29 19:14:43 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/IncompleteNextCountError.st,v 1.2 2003/08/29 19:14:43 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: IncompleteNextCountError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 IncompleteNextCountError initialize!
+
+
+
--- a/IndexNotFoundError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/IndexNotFoundError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 NotFoundError subclass:#IndexNotFoundError
@@ -44,5 +43,12 @@
 !IndexNotFoundError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/IndexNotFoundError.st,v 1.3 2003-08-29 19:14:40 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/IndexNotFoundError.st,v 1.3 2003/08/29 19:14:40 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: IndexNotFoundError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/InvalidByteCodeError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/InvalidByteCodeError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 InvalidCodeError subclass:#InvalidByteCodeError
@@ -50,7 +49,14 @@
 !InvalidByteCodeError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/InvalidByteCodeError.st,v 1.4 2003-09-05 10:28:30 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/InvalidByteCodeError.st,v 1.4 2003/09/05 10:28:30 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: InvalidByteCodeError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 InvalidByteCodeError initialize!
+
+
+
--- a/InvalidCodeError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/InvalidCodeError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ExecutionError subclass:#InvalidCodeError
@@ -50,7 +49,14 @@
 !InvalidCodeError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/InvalidCodeError.st,v 1.4 2003-09-05 10:27:13 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/InvalidCodeError.st,v 1.4 2003/09/05 10:27:13 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: InvalidCodeError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 InvalidCodeError initialize!
+
+
+
--- a/InvalidEncodingError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/InvalidEncodingError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 DecodingError subclass:#InvalidEncodingError
@@ -44,5 +43,12 @@
 !InvalidEncodingError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/InvalidEncodingError.st,v 1.3 2004-03-09 22:00:59 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/InvalidEncodingError.st,v 1.3 2004/03/09 22:00:59 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: InvalidEncodingError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/InvalidInstructionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/InvalidInstructionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 InvalidCodeError subclass:#InvalidInstructionError
@@ -50,7 +49,14 @@
 !InvalidInstructionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/InvalidInstructionError.st,v 1.4 2003-09-05 10:27:30 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/InvalidInstructionError.st,v 1.4 2003/09/05 10:27:30 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: InvalidInstructionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 InvalidInstructionError initialize!
+
+
+
--- a/InvalidModeError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/InvalidModeError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#InvalidModeError
@@ -38,5 +37,12 @@
 !InvalidModeError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/InvalidModeError.st,v 1.2 2005-02-02 10:59:58 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/InvalidModeError.st,v 1.2 2005/02/02 10:59:58 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: InvalidModeError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/InvalidOperationError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/InvalidOperationError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#InvalidOperationError
@@ -38,5 +37,12 @@
 !InvalidOperationError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/InvalidOperationError.st,v 1.2 2005-02-02 11:02:30 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/InvalidOperationError.st,v 1.2 2005/02/02 11:02:30 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: InvalidOperationError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/InvalidReadError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/InvalidReadError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ReadError subclass:#InvalidReadError
@@ -44,5 +43,12 @@
 !InvalidReadError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/InvalidReadError.st,v 1.3 2005-02-02 11:02:06 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/InvalidReadError.st,v 1.3 2005/02/02 11:02:06 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: InvalidReadError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/InvalidWriteError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/InvalidWriteError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 WriteError subclass:#InvalidWriteError
@@ -44,5 +43,12 @@
 !InvalidWriteError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/InvalidWriteError.st,v 1.3 2005-02-02 11:03:13 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/InvalidWriteError.st,v 1.3 2005/02/02 11:03:13 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: InvalidWriteError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/KeyNotFoundError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/KeyNotFoundError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 NotFoundError subclass:#KeyNotFoundError
@@ -44,5 +43,12 @@
 !KeyNotFoundError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/KeyNotFoundError.st,v 1.1 2004-04-23 11:40:02 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/KeyNotFoundError.st,v 1.1 2004/04/23 11:40:02 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: KeyNotFoundError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/LargeFloat.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/LargeFloat.st	Thu Mar 28 12:21:50 2013 +0000
@@ -735,7 +735,10 @@
 !LargeFloat class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/LargeFloat.st,v 1.7 2004-11-12 12:23:46 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/LargeFloat.st,v 1.7 2004/11/12 12:23:46 cg Exp $'
 ! !
 
 LargeFloat initialize!
+
+
+
--- a/LibraryDefinition.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/LibraryDefinition.st	Thu Mar 28 12:21:50 2013 +0000
@@ -34,6 +34,12 @@
 "
 ! !
 
+
+!LibraryDefinition class methodsFor:'code generation'!
+
+ !
+
+
 !LibraryDefinition class methodsFor:'description - compilation'!
 
 primaryTarget
@@ -42,6 +48,7 @@
     ^ 'classLibRule'
 ! !
 
+
 !LibraryDefinition class methodsFor:'description - project information'!
 
 description
@@ -73,6 +80,7 @@
     "Created: / 21-12-2010 / 09:28:59 / cg"
 ! !
 
+
 !LibraryDefinition class methodsFor:'file generation'!
 
 basicFileNamesToGenerate
@@ -116,6 +124,7 @@
     "Modified: / 19-09-2006 / 22:41:40 / cg"
 ! !
 
+
 !LibraryDefinition class methodsFor:'file mappings'!
 
 bc_dot_mak_mappings
@@ -185,6 +194,7 @@
     "Modified: / 14-09-2006 / 18:58:07 / cg"
 ! !
 
+
 !LibraryDefinition class methodsFor:'file mappings support'!
 
 commonSymbolsFlag
@@ -230,6 +240,7 @@
     "Modified: / 14-09-2006 / 14:19:59 / cg"
 ! !
 
+
 !LibraryDefinition class methodsFor:'file templates'!
 
 bc_dot_def
@@ -323,19 +334,26 @@
 
 
 %(ADDITIONAL_RULES)
+
 %(ADDITIONAL_HEADERRULES)
 
+test: $(TOP)\goodies\builder\reports\NUL
+        pushd $(TOP)\goodies\builder\reports & $(MAKE_BAT)
+        $(TOP)\goodies\builder\reports\report-runner.bat -D . -r Builder::TestReport -p $(PACKAGE)
+        
 clean::
         del *.$(CSUFFIX)
 
+
 # BEGINMAKEDEPEND --- do not remove this line; make depend needs it
 %(DEPENDENCIES)
 # ENDMAKEDEPEND --- do not remove this line
-'
+%(ADDITIONAL_RULES_HG)'
 
     "Created: / 09-08-2006 / 11:44:20 / fm"
     "Modified: / 09-08-2006 / 19:59:32 / fm"
     "Modified: / 26-07-2012 / 00:57:20 / cg"
+    "Modified: / 28-11-2012 / 10:18:59 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 extensionLine_libInit_dot_cc
@@ -463,8 +481,17 @@
 
 %(ADDITIONAL_RULES_SVN)
 
+%(ADDITIONAL_RULES_HG)
+
 %(ADDITIONAL_HEADERRULES)
 
+# run default testsuite for this package
+test: $(TOP)/goodies/builder/reports
+        $(MAKE) -C $(TOP)/goodies/builder/reports
+        $(TOP)/goodies/builder/reports/report-runner.sh -D . -r Builder::TestReport -p $(PACKAGE)
+
+
+
 # add more install actions here
 install::
 
@@ -526,6 +553,7 @@
     "Modified: / 09-08-2006 / 16:50:23 / fm"
     "Modified: / 24-06-2009 / 21:39:29 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified: / 26-07-2012 / 00:57:29 / cg"
+    "Modified: / 28-11-2012 / 10:19:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 vc_dot_def
@@ -560,6 +588,7 @@
     "Modified: / 08-08-2006 / 19:33:14 / fm"
 ! !
 
+
 !LibraryDefinition class methodsFor:'misc ui support'!
 
 iconInBrowserSymbol
@@ -575,6 +604,7 @@
 "/        ].
 ! !
 
+
 !LibraryDefinition class methodsFor:'obsolete'!
 
 lib_dot_rc
@@ -630,12 +660,14 @@
     "Modified: / 24-01-2012 / 18:35:45 / cg"
 ! !
 
+
 !LibraryDefinition class methodsFor:'queries'!
 
 projectType
     ^ LibraryType
 ! !
 
+
 !LibraryDefinition class methodsFor:'sanity checks'!
 
 searchForInconsistencies
@@ -666,6 +698,7 @@
     "Created: / 09-08-2006 / 16:31:54 / fm"
 ! !
 
+
 !LibraryDefinition class methodsFor:'testing'!
 
 isAbstract
@@ -684,6 +717,7 @@
     "Created: / 23-08-2006 / 15:17:50 / cg"
 ! !
 
+
 !LibraryDefinition class methodsFor:'documentation'!
 
 version
--- a/Link.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Link.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,6 +9,7 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
+"{ Package: 'stx:libbasic' }"
 
 Object subclass:#Link
 	instanceVariableNames:'nextLink'
@@ -62,5 +63,12 @@
 !Link class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Link.st,v 1.12 1996-04-25 16:16:29 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Link.st,v 1.12 1996/04/25 16:16:29 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: Link.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/Lookup.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Lookup.st	Thu Mar 28 12:21:50 2013 +0000
@@ -106,6 +106,15 @@
 !
 
 lookupMethodForSelector:selector directedTo:initialSearchClass for:aReceiver withArguments:argArrayOrNil from:sendingContext
+
+    <resource: #obsolete>
+
+	"
+	 This method is no longer sent by the VM as it nows pass
+	 inline/poly cache object. 
+	"
+
+
     "invoked by the VM to ask me for a method to call.
      The arguments are: the selector, receiver and arguments,
      the class to start the search in (for here-, super and directed sends)
@@ -128,6 +137,44 @@
 		   directedTo: initialSearchClass
 
 
+!
+
+lookupMethodForSelector:selector directedTo:initialSearchClass for:aReceiver withArguments:argArrayOrNil from:sendingContext ilc: ilcCache
+
+    "Invoked by the VM to ask me for a method to call.
+     The arguments are: the selector, receiver and arguments,
+     the class to start the search in (for here-, super and directed sends)
+     the sending context and the inline/poly cache (instance of
+	 PolymorphicInlineCache). 
+	 	
+     The returned method object will NOT be put into the inline- and 
+	 polyCache bu default. To update the call site's cache, you have to
+	 call ilcCache bindTo: method forClass: initialSearch class. If you
+	 dont call it, inline/poly cache won't be updated and next call
+	 won't be cached (therefore it will be relatively slow. 
+
+     If I return nil, a doesNotUnderstand: will be send."
+
+
+    | method |
+
+	"Following C code is just a performance optimization.
+	 It is not neccessary, however it speeds up UI code,
+	 since it heavily uses perform:"
+
+%{
+    method = __lookup(initialSearchClass, selector);
+    if ( method ) {
+        __ilcBind(ilcCache, initialSearchClass, method, selector);
+    }
+    RETURN (method);
+%}.
+
+    method := self lookupMethodForSelector:selector directedTo:initialSearchClass for:aReceiver withArguments:argArrayOrNil from:sendingContext.
+    ilcCache bindTo: method forClass: initialSearchClass.
+    ^ method.
+
+    "Created: / 01-10-2011 / 13:18:40 / Jan Kurs <kursjan@fit.cvut.cz>"
 ! !
 
 !Lookup class methodsFor:'documentation'!
@@ -137,7 +184,7 @@
 !
 
 version_SVN
-    ^ '§Id: Lookup.st,v 1.1 2011/06/28 10:51:38 vrany Exp §'
+    ^ '$Id: Lookup.st 10722 2011-10-13 15:42:52Z vranyj1 $'
 ! !
 
 Lookup initialize!
--- a/MacFilename.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/MacFilename.st	Thu Mar 28 12:21:50 2013 +0000
@@ -64,5 +64,8 @@
 !MacFilename class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/MacFilename.st,v 1.1 1997-09-17 17:43:58 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/MacFilename.st,v 1.1 1997/09/17 17:43:58 cg Exp $'
 ! !
+
+
+
--- a/Make.proto	Wed Mar 27 20:36:15 2013 +0100
+++ b/Make.proto	Thu Mar 28 12:21:50 2013 +0000
@@ -92,6 +92,12 @@
 
 
 
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+ifneq (**NOHG**, $(shell hg root 2> /dev/null || echo -n '**NOHG**'))
+stx_libbasic.$(O): $(shell hg root)/.hg/dirstate
+endif
 
 # add more install actions here
 install::
@@ -162,6 +168,7 @@
 $(OUTDIR)OSProcess.$(O) OSProcess.$(H): OSProcess.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ObjectMemory.$(O) ObjectMemory.$(H): ObjectMemory.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)PackageId.$(O) PackageId.$(H): PackageId.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
+$(OUTDIR)PolymorphicInlineCache.$(O) PolymorphicInlineCache.$(H): PolymorphicInlineCache.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ProcessorScheduler.$(O) ProcessorScheduler.$(H): ProcessorScheduler.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)ProgrammingLanguage.$(O) ProgrammingLanguage.$(H): ProgrammingLanguage.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
 $(OUTDIR)Project.$(O) Project.$(H): Project.st $(INCLUDE_TOP)/stx/libbasic/Object.$(H) $(STCHDR)
--- a/Make.spec	Wed Mar 27 20:36:15 2013 +0100
+++ b/Make.spec	Thu Mar 28 12:21:50 2013 +0000
@@ -380,6 +380,7 @@
 	MethodNotAppropriateError \
 	AbstractClassInstantiationError \
 	InvalidTypeError \
+	PolymorphicInlineCache \
 
 UNIX_CLASSES= \
 	UnixFileDescriptorHandle \
@@ -726,6 +727,7 @@
     $(OUTDIR_SLASH)MethodNotAppropriateError.$(O) \
     $(OUTDIR_SLASH)AbstractClassInstantiationError.$(O) \
     $(OUTDIR_SLASH)InvalidTypeError.$(O) \
+    $(OUTDIR_SLASH)PolymorphicInlineCache.$(O) \
 
 UNIX_OBJS= \
     $(OUTDIR_SLASH)UnixFileDescriptorHandle.$(O) \
--- a/MallocFailure.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/MallocFailure.st	Thu Mar 28 12:21:50 2013 +0000
@@ -41,9 +41,14 @@
 "
 ! !
 
+
 !MallocFailure class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/MallocFailure.st,v 1.3 2013-03-13 23:47:08 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: MallocFailure.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
--- a/MappedExternalBytes.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/MappedExternalBytes.st	Thu Mar 28 12:21:50 2013 +0000
@@ -83,5 +83,8 @@
 !MappedExternalBytes class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/MappedExternalBytes.st,v 1.3 2007-02-22 15:27:19 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/MappedExternalBytes.st,v 1.3 2007/02/22 15:27:19 cg Exp $'
 ! !
+
+
+
--- a/MetaNumber.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/MetaNumber.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Number subclass:#MetaNumber
@@ -119,5 +118,12 @@
 !MetaNumber class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/MetaNumber.st,v 1.1 2003-06-21 10:12:21 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/MetaNumber.st,v 1.1 2003/06/21 10:12:21 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: MetaNumber.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/Metaclass.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Metaclass.st	Thu Mar 28 12:21:50 2013 +0000
@@ -876,6 +876,14 @@
     "Created: / 01-07-2011 / 10:55:39 / cg"
 !
 
+sourceCodeManagerFromBinaryRevision
+
+    ^ myClass sourceCodeManagerFromBinaryRevision
+
+    "Modified: / 01-04-1997 / 14:36:31 / stefan"
+    "Created: / 06-10-2011 / 09:34:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 sourceFileSuffix
     ^ self programmingLanguage sourceFileSuffix
 
--- a/Method.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Method.st	Thu Mar 28 12:21:50 2013 +0000
@@ -587,17 +587,39 @@
 !
 
 overriddenMethod
+    <resource: #obsolete>
+
+    self obsoleteMethodWarning: 'Use overwrittenMethod instead, stupid naming'.
+    ^self overwrittenMethod
+
+    "Created: / 17-06-2009 / 19:09:58 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified (format): / 18-11-2011 / 14:48:07 / cg"
+    "Modified: / 05-07-2012 / 10:51:29 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+overriddenMethod: aMethod
+    <resource: #obsolete>
+
+    self obsoleteMethodWarning: 'Use overwrittenMethod: instead, stupid naming'.
+    self overwrittenMethod: aMethod
+
+    "Created: / 17-06-2009 / 19:09:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 22-08-2009 / 10:47:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 18-11-2011 / 14:48:26 / cg"
+    "Modified: / 05-07-2012 / 10:51:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+overwrittenMethod
     "Answers overridden method or nil."
 
     Overrides isNil ifTrue:[^ nil].
     ^ (Overrides includesKey: self)
         ifTrue:[Overrides at: self]
 
-    "Created: / 17-06-2009 / 19:09:58 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified (format): / 18-11-2011 / 14:48:07 / cg"
+    "Created: / 05-07-2012 / 10:49:44 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
-overriddenMethod: aMethod
+overwrittenMethod: aMethod
 
     "Set overridden method to aMethod"
 
@@ -605,9 +627,7 @@
     aMethod notNil ifTrue:[aMethod makeLocalStringSource].
     Overrides at: self put: aMethod
 
-    "Created: / 17-06-2009 / 19:09:17 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 22-08-2009 / 10:47:42 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 18-11-2011 / 14:48:26 / cg"
+    "Created: / 05-07-2012 / 10:50:00 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 package
@@ -650,6 +670,17 @@
         package := newPackage.
 
         cls := self mclass.
+        "JV@2011-01-27: BUG FIX: method may be wrapped (breakpoint on it). 
+         Search for the wrapper, if none is found, return immediately
+         (avoids DNU)"
+        cls isNil ifTrue:[
+            | wrapper |
+
+            wrapper := self wrapper.
+            wrapper isNil ifTrue:[ ^ self ].
+            cls := wrapper mclass.
+            cls isNil ifTrue:[ ^ self ].
+        ].
 
         self changed:#package.                                              "/ will vanish
         cls changed:#methodPackage with:self selector.                      "/ will vanish
@@ -659,6 +690,8 @@
     ]
 
     "Modified: / 23-11-2006 / 17:01:02 / cg"
+    "Modified: / 27-01-2012 / 17:15:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (comment): / 27-01-2012 / 21:22:40 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 setAnnotations: anObject
@@ -2024,7 +2057,7 @@
      You have to close the stream, if usingCacheBoolean is false, and should not close it
      if usingCacheBoolean is true."
 
-    |aStream fileName who myClass mgr className classNameSymbol dir mod|
+    |aStream fileName who myClass mgr className classNameSymbol dir mod pkgDef |
 
     "
      if sourcePosition is nonNil, its the fileName and
@@ -2086,7 +2119,21 @@
     "/
     "/ if there is no SourceManager, look in local standard places first
     "/
-    (Class tryLocalSourceFirst or:[(mgr := Smalltalk at:#SourceCodeManager) isNil]) ifTrue:[
+    (mclass notNil and:[package == mclass package]) ifTrue:[
+        mgr := mclass sourceCodeManagerFromBinaryRevision
+    ] ifFalse:[
+        "I'm an extension and we don't have binary revision info (!!)
+         for extensions, try tp guess here"
+        pkgDef := ProjectDefinition definitionClassForPackage: package.
+        pkgDef notNil ifTrue:[
+            mgr := pkgDef sourceCodeManagerFromBinaryRevision
+        ] ifFalse:[
+            "OK, trust the configuration"
+            mgr := AbstractSourceCodeManager managerForPackage: package
+        ]
+    ].
+
+    (Class tryLocalSourceFirst or:[mgr isNil]) ifTrue:[
         aStream := self localSourceStream.
         aStream notNil ifTrue:[
             usingCacheBoolean ifTrue:[
@@ -2755,6 +2802,18 @@
     "
 !
 
+methodArgAndVarNamesInContext: context
+    "return a collection with the methods argument and variable names.
+     Uses Parser to parse methods source and extract the names.
+     Returns nil if the source is not available, or some other
+     syntax/parse error occurred. For methods with no args and no vars,
+     an empty collection is returned."
+
+    ^self methodArgAndVarNames
+
+    "Created: / 18-12-2012 / 18:17:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 methodArgNames
     "return a collection with the methods argument names.
      Uses Parser to parse methods source and extract the names."
@@ -2881,15 +2940,25 @@
 !
 
 overrides: aMethod
+    <resource: #obsolete>
+
+    self obsoleteMethodWarning: 'Use overwrites: instead, stupid naming'.
+    self overwrites: aMethod.
+
+    "Modified: / 18-06-2009 / 12:15:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Modified: / 05-07-2012 / 10:52:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+overwrites: aMethod
 
     | mth |
-    mth := self overriddenMethod.
+    mth := self overwrittenMethod.
     [ mth notNil ] whileTrue:
         [mth == aMethod ifTrue:[^true].
-        mth := mth overriddenMethod].
+        mth := mth overwrittenMethod].
     ^false
 
-    "Modified: / 18-06-2009 / 12:15:53 / Jan Vrany <vranyj1@fel.cvut.cz>"
+    "Created: / 05-07-2012 / 10:52:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 parse:parseSelector return:accessSelector or:valueIfNoSource
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/MethodOverrideTests.st	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,61 @@
+'From Smalltalk/X, Version:6.1.1 on 02-07-2010 at 08:40:49 AM'                  !
+
+"{ Package: 'stx:libbasic' }"
+
+TestCase subclass:#MethodOverrideTests
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Kernel-Tests'
+!
+
+
+!MethodOverrideTests methodsFor:'initialization & release'!
+
+tearDown
+
+    #(methodToBeOverriden_1) do:
+        [:sel|
+        (self respondsTo: sel) ifTrue:
+            [self class removeSelector: sel]].
+
+    "Created: / 17-06-2009 / 19:36:10 / Jan Vrany <vranyj1@fel.cvut.cz>"
+! !
+
+!MethodOverrideTests methodsFor:'tests'!
+
+test_01
+
+    | oldMethod newMethod |
+    '"{ Package: ''stx:libbasic'' }"
+    !!
+    !!MethodOverridesTest methodsFor:''mock methods''!!
+
+    methodToBeOverriden_1
+        ^0
+        !! !!' readStream fileIn.
+    oldMethod := self class compiledMethodAt:#methodToBeOverriden_1.
+    self assert: self methodToBeOverriden_1 = 0.
+
+
+    '"{ Package: ''stx:goodies/sunit'' }"
+    !!
+    !!MethodOverridesTest methodsFor:''mock methods''!!
+
+    methodToBeOverriden_1
+        ^1
+    !! !!' readStream fileIn.
+
+    self assert: self methodToBeOverriden_1 = 1.
+    newMethod := self class compiledMethodAt:#methodToBeOverriden_1.
+
+    self assert: newMethod overridenMethod == oldMethod.
+
+    "Created: / 17-06-2009 / 19:27:23 / Jan Vrany <vranyj1@fel.cvut.cz>"
+! !
+
+!MethodOverrideTests class methodsFor:'documentation'!
+
+version
+    ^'$Id: MethodOverrideTests.st 10717 2011-10-11 15:53:59Z vranyj1 $'
+! !
--- a/MiniInspector.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/MiniInspector.st	Thu Mar 28 12:21:50 2013 +0000
@@ -44,6 +44,7 @@
 "
 ! !
 
+
 !MiniInspector class methodsFor:'instance creation'!
 
 openOn:anObject
@@ -54,6 +55,7 @@
     ^ anInspector
 ! !
 
+
 !MiniInspector methodsFor:'private'!
 
 commandLoop
@@ -259,9 +261,14 @@
     "Modified: 20.5.1996 / 10:27:45 / cg"
 ! !
 
+
 !MiniInspector class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/MiniInspector.st,v 1.27 2013-03-24 11:41:25 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: MiniInspector.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
--- a/MiniLogger.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/MiniLogger.st	Thu Mar 28 12:21:50 2013 +0000
@@ -34,6 +34,7 @@
 "
 ! !
 
+
 !MiniLogger class methodsFor:'instance creation'!
 
 instance
@@ -52,6 +53,7 @@
     "Created: / 14-09-2011 / 21:27:51 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !MiniLogger class methodsFor:'class initialization'!
 
 initialize
@@ -61,6 +63,7 @@
     "Created: / 01-09-2011 / 12:26:17 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !MiniLogger methodsFor:'logging'!
 
 facilityOf: originator
@@ -165,6 +168,7 @@
     "Modified: / 15-03-2013 / 11:20:30 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !MiniLogger class methodsFor:'documentation'!
 
 version
--- a/NaiveRomanNumberFormatNotification.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/NaiveRomanNumberFormatNotification.st	Thu Mar 28 12:21:50 2013 +0000
@@ -49,5 +49,8 @@
 !NaiveRomanNumberFormatNotification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NaiveRomanNumberFormatNotification.st,v 1.3 2008-08-06 09:53:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/NaiveRomanNumberFormatNotification.st,v 1.3 2008/08/06 09:53:07 cg Exp $'
 ! !
+
+
+
--- a/NoByteCodeError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/NoByteCodeError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 InvalidCodeError subclass:#NoByteCodeError
@@ -50,7 +49,14 @@
 !NoByteCodeError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NoByteCodeError.st,v 1.4 2003-09-05 10:27:06 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/NoByteCodeError.st,v 1.4 2003/09/05 10:27:06 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: NoByteCodeError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 NoByteCodeError initialize!
+
+
+
--- a/NonBooleanReceiverError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/NonBooleanReceiverError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ExecutionError subclass:#NonBooleanReceiverError
@@ -50,7 +49,14 @@
 !NonBooleanReceiverError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NonBooleanReceiverError.st,v 1.4 2003-09-05 10:27:38 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/NonBooleanReceiverError.st,v 1.4 2003/09/05 10:27:38 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: NonBooleanReceiverError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 NonBooleanReceiverError initialize!
+
+
+
--- a/NonIntegerIndexError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/NonIntegerIndexError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 IndexNotFoundError subclass:#NonIntegerIndexError
@@ -45,5 +44,12 @@
 !NonIntegerIndexError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NonIntegerIndexError.st,v 1.3 2003-08-29 19:15:18 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/NonIntegerIndexError.st,v 1.3 2003/08/29 19:15:18 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: NonIntegerIndexError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/NotANumber.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/NotANumber.st	Thu Mar 28 12:21:50 2013 +0000
@@ -157,7 +157,10 @@
 !NotANumber class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NotANumber.st,v 1.2 2003-07-02 09:52:32 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/NotANumber.st,v 1.2 2003/07/02 09:52:32 cg Exp $'
 ! !
 
 NotANumber initialize!
+
+
+
--- a/NotFoundError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/NotFoundError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#NotFoundError
@@ -44,5 +43,12 @@
 !NotFoundError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NotFoundError.st,v 1.4 2004-08-22 17:47:38 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/NotFoundError.st,v 1.4 2004/08/22 17:47:38 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: NotFoundError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/NumberConversionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/NumberConversionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -37,5 +37,9 @@
 !NumberConversionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NumberConversionError.st,v 1.4 2008-08-06 09:53:01 cg Exp $'
+    ^ '$Id: NumberConversionError.st 10808 2012-05-09 15:04:12Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id: NumberConversionError.st 10808 2012-05-09 15:04:12Z vranyj1 $'
 ! !
--- a/NumberFormatError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/NumberFormatError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -37,5 +37,9 @@
 !NumberFormatError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/NumberFormatError.st,v 1.3 2008-08-06 09:52:56 cg Exp $'
+    ^ '$Id: NumberFormatError.st 10808 2012-05-09 15:04:12Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id: NumberFormatError.st 10808 2012-05-09 15:04:12Z vranyj1 $'
 ! !
--- a/OSFileHandle.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OSFileHandle.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OSHandle subclass:#OSFileHandle
@@ -131,7 +130,14 @@
 !OSFileHandle class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OSFileHandle.st,v 1.7 2006-02-08 18:27:09 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OSFileHandle.st,v 1.7 2006/02/08 18:27:09 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OSFileHandle.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 OSFileHandle initialize!
+
+
+
--- a/OSHandle.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OSHandle.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ExternalAddress subclass:#OSHandle
@@ -102,7 +101,14 @@
 !OSHandle class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OSHandle.st,v 1.11 2006-02-08 18:27:36 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OSHandle.st,v 1.11 2006/02/08 18:27:36 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OSHandle.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 OSHandle initialize!
+
+
+
--- a/OSSignalInterrupt.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OSSignalInterrupt.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#OSSignalInterrupt
@@ -62,7 +61,14 @@
 !OSSignalInterrupt class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OSSignalInterrupt.st,v 1.4 2005-04-11 08:53:28 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OSSignalInterrupt.st,v 1.4 2005/04/11 08:53:28 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: OSSignalInterrupt.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 OSSignalInterrupt initialize!
+
+
+
--- a/OpenVMSFileHandle.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OpenVMSFileHandle.st	Thu Mar 28 12:21:50 2013 +0000
@@ -53,5 +53,8 @@
 !OpenVMSFileHandle class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OpenVMSFileHandle.st,v 1.1 1999-09-18 11:11:28 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OpenVMSFileHandle.st,v 1.1 1999/09/18 11:11:28 cg Exp $'
 ! !
+
+
+
--- a/OpenVMSFilename.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OpenVMSFilename.st	Thu Mar 28 12:21:50 2013 +0000
@@ -1170,5 +1170,8 @@
 !OpenVMSFilename class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OpenVMSFilename.st,v 1.18 1997-10-16 10:41:25 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OpenVMSFilename.st,v 1.18 1997/10/16 10:41:25 cg Exp $'
 ! !
+
+
+
--- a/OsError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OsError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Error subclass:#OsError
@@ -44,5 +43,12 @@
 !OsError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OsError.st,v 1.3 2003-08-30 12:31:08 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OsError.st,v 1.3 2003/08/30 12:31:08 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OsError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/OsIllegalOperation.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OsIllegalOperation.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OsError subclass:#OsIllegalOperation
@@ -38,5 +37,12 @@
 !OsIllegalOperation class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OsIllegalOperation.st,v 1.3 2003-08-30 12:31:20 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OsIllegalOperation.st,v 1.3 2003/08/30 12:31:20 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OsIllegalOperation.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/OsInaccessibleError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OsInaccessibleError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OsError subclass:#OsInaccessibleError
@@ -38,5 +37,12 @@
 !OsInaccessibleError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OsInaccessibleError.st,v 1.3 2003-08-30 12:31:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OsInaccessibleError.st,v 1.3 2003/08/30 12:31:14 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OsInaccessibleError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/OsInvalidArgumentsError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OsInvalidArgumentsError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OsError subclass:#OsInvalidArgumentsError
@@ -38,5 +37,12 @@
 !OsInvalidArgumentsError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OsInvalidArgumentsError.st,v 1.3 2003-08-30 12:31:17 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OsInvalidArgumentsError.st,v 1.3 2003/08/30 12:31:17 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OsInvalidArgumentsError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/OsNeedRetryError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OsNeedRetryError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OsError subclass:#OsNeedRetryError
@@ -38,5 +37,12 @@
 !OsNeedRetryError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OsNeedRetryError.st,v 1.3 2003-08-30 12:31:04 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OsNeedRetryError.st,v 1.3 2003/08/30 12:31:04 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OsNeedRetryError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/OsNoResourcesError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OsNoResourcesError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OsError subclass:#OsNoResourcesError
@@ -38,5 +37,12 @@
 !OsNoResourcesError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OsNoResourcesError.st,v 1.3 2003-08-30 12:31:11 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OsNoResourcesError.st,v 1.3 2003/08/30 12:31:11 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OsNoResourcesError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/OsNotification.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OsNotification.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OsError subclass:#OsNotification
@@ -38,5 +37,12 @@
 !OsNotification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OsNotification.st,v 1.3 2003-08-30 12:31:22 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OsNotification.st,v 1.3 2003/08/30 12:31:22 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OsNotification.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/OsTransferFaultError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OsTransferFaultError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OsError subclass:#OsTransferFaultError
@@ -38,5 +37,12 @@
 !OsTransferFaultError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OsTransferFaultError.st,v 1.3 2003-08-30 12:31:25 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OsTransferFaultError.st,v 1.3 2003/08/30 12:31:25 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OsTransferFaultError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/OverflowError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/OverflowError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -41,16 +41,22 @@
 "
 ! !
 
+
 !OverflowError class methodsFor:'initialization'!
 
 initialize
     NotifierString := 'overflow'.
 ! !
 
+
 !OverflowError class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/OverflowError.st,v 1.4 2013-03-13 23:43:48 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: OverflowError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 
--- a/PeekableStream.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/PeekableStream.st	Thu Mar 28 12:21:50 2013 +0000
@@ -369,154 +369,11 @@
      return the value of the last chunk.
      Someone (which is usually some codeView) is notified of errors."
 
-    |lastValue pkg nameSpace usedNameSpaces
-     packageQuerySignal nameSpaceQuerySignal usedNameSpaceQuerySignal
-     changeDefaultApplicationNotificationSignal
-     defaultApplicationQuerySignal defaultApplication
-     confirmationQuerySignal handledSignals passedSignals askSomeoneForPackage outerContext askForVariableTypeOfUndeclaredQuery|
-
-    self skipSeparators.
-    lastValue := self peek.
-    lastValue == $< ifTrue:[
-        "/ assume, it's an xml file
-        ^ self fileInXMLNotifying:someone passChunk:passChunk.
-    ].
-    lastValue == $# ifTrue:[
-        "assume unix interpreter name:
-         '#!!stx -e' or something like this"
-        self nextPeek == $!! ifTrue:[
-            "skip the unix command line"
-            self nextLine
-        ] ifFalse:[
-             self error:'Invalid chunk start'
-        ]
-    ].
-
-    Smalltalk::Compiler isNil ifTrue:[
-        self isFileStream ifTrue:[
-            Transcript show:('[' , self pathName , '] ').
-        ].
-        Transcript showCR:'cannot fileIn (no compiler).'.
-        ^ nil.
-    ].
-
-    "/ support for V'Age applications
-    defaultApplicationQuerySignal := Class defaultApplicationQuerySignal.
-    changeDefaultApplicationNotificationSignal := Class changeDefaultApplicationNotificationSignal.
-
-    "/ support for ST/X's nameSpaces & packages
-    packageQuerySignal := Class packageQuerySignal.
-    nameSpaceQuerySignal := Class nameSpaceQuerySignal.
-    usedNameSpaceQuerySignal := Class usedNameSpaceQuerySignal.
-
-    (someone respondsTo:#packageToInstall) ifTrue:[
-        pkg := someone packageToInstall.
-        askSomeoneForPackage := true.
-    ] ifFalse:[
-        pkg := packageQuerySignal query.
-        askSomeoneForPackage := false.
-    ].
-    (someone respondsTo:#currentNameSpace) ifTrue:[
-        nameSpace := someone currentNameSpace
-    ] ifFalse:[
-        nameSpace := nameSpaceQuerySignal query.
-    ].
-    (someone respondsTo:#usedNameSpaces) ifTrue:[
-        usedNameSpaces := someone usedNameSpaces
-    ] ifFalse:[
-        usedNameSpaces := usedNameSpaceQuerySignal query.
-    ].
-    (someone respondsTo:#defaultApplication) ifTrue:[
-        defaultApplication := someone defaultApplication
-    ] ifFalse:[
-        defaultApplication := defaultApplicationQuerySignal query.
-    ].
-
-    confirmationQuerySignal := Metaclass confirmationQuerySignal.
-
-    handledSignals := SignalSet new.
-    passedSignals := IdentitySet new.
-
-    handledSignals add:changeDefaultApplicationNotificationSignal.
-    passedSignals add:changeDefaultApplicationNotificationSignal.
-    handledSignals add:defaultApplicationQuerySignal.
-    passedSignals add:defaultApplicationQuerySignal.
+     ^(EncodedStream decodedStreamFor:self) basicFileInNotifying:someone passChunk:passChunk
 
-    handledSignals add:packageQuerySignal.
-    handledSignals add:usedNameSpaceQuerySignal.
-    handledSignals add:nameSpaceQuerySignal.
-    handledSignals add:confirmationQuerySignal.
-    passedSignals add:confirmationQuerySignal.
-    Parser notNil ifTrue:[
-        "only if libcomp is present"
-        "Also catch a 'Parser askForVariableTypeOfUndeclaredQuery' and proceed with nil. 
-         Imagine somebody has autodefine workspace variables on and then 
-         evaluate Smalltalk loadPackage:'xyz' that loads code from source (using file-in), 
-         certainly we don't want to compile workspace variable access for every
-         not-yet-loaded class in some namespace. 
-         This is demonstrated by Regression::CompilerTests2>>test_01 
-         and this change actually fixes this test."
-        askForVariableTypeOfUndeclaredQuery := Parser askForVariableTypeOfUndeclaredQuery.
-        handledSignals add:askForVariableTypeOfUndeclaredQuery.
-    ].
-
-
-    outerContext := thisContext.
-
-    handledSignals handle:[:ex |
-        |sig|
-
-        sig := ex signal.
-        ((passedSignals includes:sig) and:[sig isHandledIn:outerContext]) ifTrue:[
-            ex reject
-        ].
-        
-        sig == changeDefaultApplicationNotificationSignal ifTrue:[
-            "/ invoked via #becomeDefault to set the defaultApp and the package.
-            "/ (only when filing in V'Age code)
-            defaultApplication := ex parameter.
-            pkg := defaultApplication name asSymbol.
-            ex proceedWith:nil
-        ].
-        sig == defaultApplicationQuerySignal ifTrue:[
-            "/ query for the application to add classes & methods into
-            "/ (only when filing in V'Age code)
-            ex proceedWith:defaultApplication
-        ].
-        sig == packageQuerySignal ifTrue:[
-            "answer the package to use for classes & methods"
-            askSomeoneForPackage ifTrue:[
-                ex proceedWith:someone packageToInstall
-            ] ifFalse:[
-                ex proceedWith:pkg
-            ]
-        ].
-        sig == usedNameSpaceQuerySignal ifTrue:[
-            "answer the nameSpaces to be searched when encountering globals"
-            ex proceedWith:usedNameSpaces
-        ].
-        sig == nameSpaceQuerySignal ifTrue:[
-            "answer the nameSpace to install new classes in"
-            ex proceedWith:nameSpace
-        ].
-        sig == confirmationQuerySignal ifTrue:[
-            "don't pop up dialogs"
-            ex proceedWith:false
-        ].
-        sig == askForVariableTypeOfUndeclaredQuery ifTrue:[
-           "no autodefined variables or so"
-            ex proceedWith:nil.
-        ].
-    ] do:[
-        [self atEnd] whileFalse:[
-            lastValue := self fileInNextChunkNotifying:someone passChunk:passChunk
-        ]
-    ].
-    ^ lastValue
-
-    "Modified: / 10.9.1999 / 16:54:01 / stefan"
-    "Modified: / 16.11.2001 / 16:21:28 / cg"
-    "Modified: / 18-03-2013 / 17:45:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 10-09-1999 / 16:54:01 / stefan"
+    "Modified: / 16-11-2001 / 16:21:28 / cg"
+    "Modified: / 25-03-2013 / 22:57:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 fileInNextChunkNotifying:someone
@@ -1046,6 +903,11 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic/PeekableStream.st,v 1.42 2013-03-19 13:15:55 stefan Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
--- a/Point.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Point.st	Thu Mar 28 12:21:50 2013 +0000
@@ -1184,7 +1184,14 @@
 !Point class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Point.st,v 1.73 2009-05-26 06:31:07 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Point.st,v 1.73 2009/05/26 06:31:07 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: Point.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 Point initialize!
+
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/PolymorphicInlineCache.st	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,106 @@
+"
+ COPYRIGHT (c) 2011 by Jan Vrany & Jan Kurs
+                       SWING Research Group, Czech Technical University in Prague
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+"
+"{ Package: 'stx:libbasic' }"
+
+Object subclass:#PolymorphicInlineCache
+	instanceVariableNames:'address numArgs'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Kernel-Classes'
+!
+
+!PolymorphicInlineCache class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 2011 by Jan Vrany & Jan Kurs
+                       SWING Research Group, Czech Technical University in Prague
+
+ Permission is hereby granted, free of charge, to any person
+ obtaining a copy of this software and associated documentation
+ files (the 'Software'), to deal in the Software without
+ restriction, including without limitation the rights to use,
+ copy, modify, merge, publish, distribute, sublicense, and/or sell
+ copies of the Software, and to permit persons to whom the
+ Software is furnished to do so, subject to the following
+ conditions:
+
+ The above copyright notice and this permission notice shall be
+ included in all copies or substantial portions of the Software.
+
+ THE SOFTWARE IS PROVIDED 'AS IS', WITHOUT WARRANTY OF ANY KIND,
+ EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES
+ OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND
+ NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT
+ HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY,
+ WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING
+ FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR
+ OTHER DEALINGS IN THE SOFTWARE.
+
+"
+!
+
+documentation
+"
+    This class provides a basic access to inline cache structure as
+    used by the virtual machine.
+
+    [author:]
+        Jan Vrany <jan.vrany@fit.cvut.cz>
+        Janb Kurs <kursjan@fit.cvut.cz>
+
+    [instance variables:]
+        address     <ExternalAddress> a pointer to the VM inline cache structure.
+                                    if the adress is NULL, then PolymorphicInlineCache
+                                    is invalid.
+        numArgs    <SmallInteger> a number of arguments
+    [class variables:]
+
+    [see also:]
+
+"
+! !
+
+!PolymorphicInlineCache methodsFor:'binding / unbinding'!
+
+bindTo: aMethod forClass: aClass
+
+    | selector |
+    selector := aMethod selector.
+%{
+	__ilcBind(self, aClass, aMethod,  selector);
+    RETURN(self);
+%}.
+    self primitiveFailed.
+
+    "Created: / 02-10-2011 / 18:05:26 / Jan Kurs <kursjan@fit.cvut.cz>"
+! !
+
+!PolymorphicInlineCache class methodsFor:'documentation'!
+
+version_SVN
+    ^ '$Id: PolymorphicInlineCache.st 10712 2011-10-04 21:59:41Z kursjan $'
+! !
--- a/PositionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/PositionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#PositionError
@@ -38,5 +37,12 @@
 !PositionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/PositionError.st,v 1.2 2005-02-02 11:02:33 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/PositionError.st,v 1.2 2005/02/02 11:02:33 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: PositionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/PositionOutOfBoundsError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/PositionOutOfBoundsError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#PositionOutOfBoundsError
@@ -44,5 +43,12 @@
 !PositionOutOfBoundsError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/PositionOutOfBoundsError.st,v 1.3 2003-08-29 19:14:46 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/PositionOutOfBoundsError.st,v 1.3 2003/08/29 19:14:46 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: PositionOutOfBoundsError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/PrimitiveFailure.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/PrimitiveFailure.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ExecutionError subclass:#PrimitiveFailure
@@ -60,5 +59,12 @@
 !PrimitiveFailure class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/PrimitiveFailure.st,v 1.7 2005-11-08 11:10:37 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/PrimitiveFailure.st,v 1.7 2005/11/08 11:10:37 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: PrimitiveFailure.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/PrivateMetaclass.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/PrivateMetaclass.st	Thu Mar 28 12:21:50 2013 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1996 by eXept Software AG
               All Rights Reserved
@@ -11,9 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
-
-
 "{ Package: 'stx:libbasic' }"
 
 Metaclass subclass:#PrivateMetaclass
@@ -132,5 +127,12 @@
 !PrivateMetaclass class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/PrivateMetaclass.st,v 1.13 2004-03-05 17:53:16 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/PrivateMetaclass.st,v 1.13 2004/03/05 17:53:16 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: PrivateMetaclass.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/ProceedError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ProceedError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,9 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
-
-
 "{ Package: 'stx:libbasic' }"
 
 Warning subclass:#ProceedError
@@ -100,7 +97,14 @@
 !ProceedError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ProceedError.st,v 1.5 2003-08-29 19:14:59 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ProceedError.st,v 1.5 2003/08/29 19:14:59 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: ProceedError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 ProceedError initialize!
+
+
+
--- a/ProjectDefinition.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ProjectDefinition.st	Thu Mar 28 12:21:50 2013 +0000
@@ -831,6 +831,7 @@
     "Created: / 14-09-2006 / 14:59:53 / cg"
 ! !
 
+
 !ProjectDefinition class methodsFor:'accessing - packaging'!
 
 classNames:aCollectionOfClassNames
@@ -970,6 +971,7 @@
         inCategory:'description - contents'.
 ! !
 
+
 !ProjectDefinition class methodsFor:'accessing - tests'!
 
 excludedFromTestSuite
@@ -988,14 +990,14 @@
 
     suite := TestSuite named:self package.
     classes := self classes
-                select:[:each |
-                    [
-                    each isLoaded ifFalse:[each autoload].
-                    (each isTestCaseLike) and:[ each isAbstract not ]
-                    ] on: Autoload autoloadFailedSignal do:[
-                        false
-                    ]
-                ].
+		select:[:each |
+		    [
+		    each isLoaded ifFalse:[each autoload].
+		    (each isTestCaseLike) and:[ each isAbstract not ]
+		    ] on: Autoload autoloadFailedSignal do:[
+			false
+		    ]
+		].
 
     classes := classes asSortedCollection:[:a :b | a name <= b name ].
     classes do: [:eachClass |
@@ -1716,6 +1718,7 @@
     "Modified: / 29-03-2012 / 18:43:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !ProjectDefinition class methodsFor:'defaults'!
 
 applicationTypes
@@ -1932,6 +1935,7 @@
     "Modified: / 17-08-2006 / 19:59:26 / cg"
 ! !
 
+
 !ProjectDefinition class methodsFor:'description - classes'!
 
 additionalClassNamesAndAttributes
@@ -4397,7 +4401,11 @@
 @REM type bmake, and wait...
 @REM do not edit - automatically generated from ProjectDefinition
 @REM -------
-make.exe -N -f bc.mak %%*
+@SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%%%i in (''hg root'') do SET HGROOT=%%%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+make.exe -N -f bc.mak  %DEFINES% %*
 
 %(SUBPROJECT_BMAKE_CALLS)
 '
@@ -4582,16 +4590,21 @@
 @REM type mingwmake, and wait...
 @REM do not edit - automatically generated from ProjectDefinition
 @REM -------
+@SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%%%i in (''hg root'') do SET HGROOT=%%%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
 
 @pushd %(TOP)\rules
 @call find_mingw.bat
 @popd
-make.exe -N -f bc.mak %%USEMINGW_ARG%% %%*
+make.exe -N -f bc.mak %DEFINES% %%USEMINGW_ARG%% %%*
 
 %(SUBPROJECT_MINGWMAKE_CALLS)
 '
 
     "Created: / 05-09-2012 / 19:44:51 / cg"
+    "Modified: / 19-03-2013 / 08:54:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 objectLine_make_dot_spec
@@ -4699,7 +4712,13 @@
     call vcsetup.bat
     popd
 )
-make.exe -N -f bc.mak -DUSEVC %%*
+@SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%%%i in (''hg root'') do SET HGROOT=%%%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+make.exe -N -f bc.mak -DUSEVC=1 %DEFINES% %*
+
+
 
 %(SUBPROJECT_VCMAKE_CALLS)
 '
@@ -4773,71 +4792,76 @@
         ^ false
     ].
 
-    newStuffHasBeenLoaded := false.
-
-    (self infoPrinting and:[Smalltalk silentLoading not]) ifTrue:[
-        "/ thisContext fullPrintAll.
-        Transcript showCR:('loading %1%2...'
-                            bindWith:(asAutoloaded ifTrue:['as autoloaded '] ifFalse:[''])
-                            with:self name).
+    [
+        PackagesBeingLoaded add:self package.
+
+        newStuffHasBeenLoaded := false.
+
+        (self infoPrinting and:[Smalltalk silentLoading not]) ifTrue:[
+            "/ thisContext fullPrintAll.
+            Transcript showCR:('loading %1%2...'
+                                bindWith:(asAutoloaded ifTrue:['as autoloaded '] ifFalse:[''])
+                                with:self name).
+        ].
+
+        self rememberOverwrittenExtensionMethods.
+
+        self activityNotification:'Executing pre-load action'.
+        self executeHooks: #preLoad.
+        self preLoadAction.
+
+        meOrMySecondIncarnation := self.
+
+        Class withoutUpdatingChangesDo:[
+            self activityNotification:'Loading prerequisities'.
+            self loadPreRequisitesAsAutoloaded:asAutoloaded.
+
+            self checkPrerequisitesForLoading.
+
+            asAutoloaded ifFalse:[
+                self loadClassLibrary.
+                "/ could have overloaded my first incarnation
+                meOrMySecondIncarnation := (Smalltalk at:(self name)) ? self.
+                meOrMySecondIncarnation ~~ self ifTrue:[
+                    meOrMySecondIncarnation fetchSlotsFrom:self.
+                ].
+            ].
+
+            self hasAllExtensionsLoaded ifFalse:[
+                self activityNotification:'Loading extensions'.
+                newStuffHasBeenLoaded := newStuffHasBeenLoaded | meOrMySecondIncarnation loadExtensions.
+            ].
+            self hasAllClassesLoaded ifFalse:[
+                self activityNotification:'Loading classes'.
+                newStuffHasBeenLoaded := newStuffHasBeenLoaded | (meOrMySecondIncarnation loadAllClassesAsAutoloaded:asAutoloaded).
+            ].
+     "/ no, don't load subProjects here - will lead to a recursion, which leads
+     "/ to some classes being loaded from source (soap)
+            self activityNotification:'Loading sub projects'.
+            meOrMySecondIncarnation loadSubProjectsAsAutoloaded:asAutoloaded.
+        ].
+        self activityNotification:('Executing post-load action for %1' bindWith:self package).
+
+        "/ mhmh - already done for dll-loaded packages
+        "/ meOrMySecondIncarnation initializeAllClasses.
+        meOrMySecondIncarnation postLoadAction.
+        meOrMySecondIncarnation executeHooks: #postLoad.
+
+        meOrMySecondIncarnation projectIsLoaded:true.
+        meOrMySecondIncarnation ~~ self ifTrue:[
+            self projectIsLoaded:true.
+        ].
+
+        self activityNotification:('Done (%1).' bindWith:self package).
+    ] ensure: [
+        PackagesBeingLoaded remove:self package ifAbsent:[]
     ].
-
-    self rememberOverwrittenExtensionMethods.
-
-    self activityNotification:'Executing pre-load action'.
-    self executeHooks: #preLoad.
-    self preLoadAction.
-
-    meOrMySecondIncarnation := self.
-
-    Class withoutUpdatingChangesDo:[
-        self activityNotification:'Loading prerequisities'.
-        self loadPreRequisitesAsAutoloaded:asAutoloaded.
-
-        self checkPrerequisitesForLoading.
-
-        asAutoloaded ifFalse:[
-            self loadClassLibrary.
-            "/ could have overloaded my first incarnation
-            meOrMySecondIncarnation := (Smalltalk at:(self name)) ? self.
-            meOrMySecondIncarnation ~~ self ifTrue:[
-                meOrMySecondIncarnation fetchSlotsFrom:self.
-            ].
-        ].
-
-        self hasAllExtensionsLoaded ifFalse:[
-            self activityNotification:'Loading extensions'.
-            newStuffHasBeenLoaded := newStuffHasBeenLoaded | meOrMySecondIncarnation loadExtensions.
-        ].
-        self hasAllClassesLoaded ifFalse:[
-            self activityNotification:'Loading classes'.
-            newStuffHasBeenLoaded := newStuffHasBeenLoaded | (meOrMySecondIncarnation loadAllClassesAsAutoloaded:asAutoloaded).
-        ].
-"/ no, don't load subProjects here - will lead to a recursion, which leads
-"/ to some classes being loaded from source (soap)
-        self activityNotification:'Loading sub projects'.
-        meOrMySecondIncarnation loadSubProjectsAsAutoloaded:asAutoloaded.
-    ].
-    self activityNotification:('Executing post-load action for %1' bindWith:self package).
-
-    "/ mhmh - already done for dll-loaded packages
-    "/ meOrMySecondIncarnation initializeAllClasses.
-    meOrMySecondIncarnation postLoadAction.
-    meOrMySecondIncarnation executeHooks: #postLoad.
-
-    meOrMySecondIncarnation projectIsLoaded:true.
-    meOrMySecondIncarnation ~~ self ifTrue:[
-        self projectIsLoaded:true.
-    ].
-
-    self activityNotification:('Done (%1).' bindWith:self package).
     ^ newStuffHasBeenLoaded
 
     "Created: / 17-08-2006 / 01:01:41 / cg"
     "Modified: / 30-10-2008 / 08:16:21 / Jan Vrany <vranyj1@fel.cvut.cz>"
-    "Modified: / 22-08-2009 / 12:02:14 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 04-09-2011 / 10:01:53 / cg"
-    "Modified: / 20-11-2012 / 23:06:32 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 21-03-2013 / 09:21:43 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 unloadPackage
@@ -4940,10 +4964,15 @@
      test resources, as they are not neccessary for the package
      and should not be compiled (because of unwanted dependency
      on stx:goodies/sunit package)
-    "
-
-    (aClass inheritsFrom: TestCase) ifTrue:[^#(autoload)].
-    (aClass inheritsFrom: TestResource) ifTrue:[^#(autoload)].
+
+     But not make them autoloaded when the package is separate
+     test-package - by conventions such package should by named
+     #'module:package/subpackage/tests'    
+    "
+    ((self package endsWith: '/tests') or:[(self package endsWith: '/tests')]) ifFalse:[
+        (aClass inheritsFrom: TestCase) ifTrue:[^#(autoload)].
+        (aClass inheritsFrom: TestResource) ifTrue:[^#(autoload)].
+    ].
 
     "No additional attributes"
     ^#()
@@ -4959,6 +4988,7 @@
     "
 
     "Created: / 26-10-2009 / 12:54:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified: / 20-03-2013 / 19:33:58 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 checkIfClassesArePresent
@@ -5914,6 +5944,20 @@
     "Created: / 17-08-2006 / 00:21:39 / cg"
 !
 
+loadExtensionsForLanguage: lang
+    "load extension methods for given programming language"
+
+    | filename file |
+    filename := 'extensions.' , lang sourceFileSuffix.
+    file := self packageDirectory / filename.
+    file exists ifTrue:[
+        lang fileIn: file.
+    ]
+
+    "Created: / 17-08-2006 / 00:21:39 / cg"
+    "Created: / 25-11-2011 / 18:13:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 loadPackages:aListOfPackages asAutoloaded:asAutoloaded
     "load some packages (at least the projectDefinitions and their extensions).
      If asAutoloaded == true, classes will be only installed as autoloaded."
@@ -5927,19 +5971,13 @@
 
             cls := self definitionClassForPackage:eachPackageID.
             (cls isNil or:[cls isLoaded not or:[cls projectIsLoaded not]]) ifTrue:[                        
-                (PackagesBeingLoaded includes:eachPackageID) ifFalse:[
-                    PackagesBeingLoaded add:eachPackageID.
-                    [
-                        Smalltalk loadPackage:eachPackageID asAutoloaded:asAutoloaded.
-                    ] ensure:[
-                        PackagesBeingLoaded remove:eachPackageID ifAbsent:[].
-                    ]
-                ]
+                Smalltalk loadPackage:eachPackageID asAutoloaded:asAutoloaded.
             ]
         ].
     ].
 
     "Modified: / 09-12-2010 / 12:36:17 / cg"
+    "Modified: / 21-03-2013 / 09:22:24 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 loadPreRequisitesAsAutoloaded:asAutoloaded
@@ -7176,6 +7214,11 @@
     ^ '$Header: /cvs/stx/stx/libbasic/ProjectDefinition.st,v 1.444 2013-03-27 19:36:15 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '§ Id: ProjectDefinition.st 10645 2011-06-09 15:28:45Z vranyj1  §'
 ! !
--- a/QualifiedName.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/QualifiedName.st	Thu Mar 28 12:21:50 2013 +0000
@@ -116,5 +116,8 @@
 !QualifiedName class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/QualifiedName.st,v 1.2 2000-04-12 21:38:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/QualifiedName.st,v 1.2 2000/04/12 21:38:35 cg Exp $'
 ! !
+
+
+
--- a/QueryWithoutDefault.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/QueryWithoutDefault.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Query subclass:#QueryWithoutDefault
@@ -83,7 +82,14 @@
 !QueryWithoutDefault class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/QueryWithoutDefault.st,v 1.3 2005-01-20 12:26:17 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/QueryWithoutDefault.st,v 1.3 2005/01/20 12:26:17 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: QueryWithoutDefault.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 QueryWithoutDefault initialize!
+
+
+
--- a/RangeError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/RangeError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -41,16 +41,22 @@
 "
 ! !
 
+
 !RangeError class methodsFor:'initialization'!
 
 initialize
     NotifierString := 'numeric range error'.
 ! !
 
+
 !RangeError class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/RangeError.st,v 1.5 2013-03-13 23:43:54 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: RangeError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 
--- a/ReadError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ReadError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#ReadError
@@ -38,5 +37,12 @@
 !ReadError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ReadError.st,v 1.2 2005-02-02 10:59:36 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ReadError.st,v 1.2 2005/02/02 10:59:36 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: ReadError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/ReadOnlySequenceableCollection.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ReadOnlySequenceableCollection.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 SequenceableCollection subclass:#ReadOnlySequenceableCollection
@@ -106,5 +105,12 @@
 !ReadOnlySequenceableCollection class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ReadOnlySequenceableCollection.st,v 1.4 2005-06-27 10:24:03 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ReadOnlySequenceableCollection.st,v 1.4 2005/06/27 10:24:03 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: ReadOnlySequenceableCollection.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/RecursionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/RecursionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Error subclass:#RecursionError
@@ -55,5 +54,12 @@
 !RecursionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/RecursionError.st,v 1.5 2003-08-29 19:14:56 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/RecursionError.st,v 1.5 2003/08/29 19:14:56 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: RecursionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/RecursiveExceptionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/RecursiveExceptionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,9 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
-
-
 "{ Package: 'stx:libbasic' }"
 
 Error subclass:#RecursiveExceptionError
@@ -75,7 +72,14 @@
 !RecursiveExceptionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/RecursiveExceptionError.st,v 1.5 2005-09-30 13:37:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/RecursiveExceptionError.st,v 1.5 2005/09/30 13:37:54 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: RecursiveExceptionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 RecursiveExceptionError initialize!
+
+
+
--- a/RestartProcessRequest.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/RestartProcessRequest.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ControlRequest subclass:#RestartProcessRequest
@@ -45,5 +44,12 @@
 !RestartProcessRequest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/RestartProcessRequest.st,v 1.2 2003-08-29 19:18:11 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/RestartProcessRequest.st,v 1.2 2003/08/29 19:18:11 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: RestartProcessRequest.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/RomanNumberFormatError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/RomanNumberFormatError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -49,5 +49,9 @@
 !RomanNumberFormatError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/RomanNumberFormatError.st,v 1.4 2008-08-06 09:53:04 cg Exp $'
+    ^ '$Id: RomanNumberFormatError.st 10808 2012-05-09 15:04:12Z vranyj1 $'
+!
+
+version_SVN
+    ^ '$Id: RomanNumberFormatError.st 10808 2012-05-09 15:04:12Z vranyj1 $'
 ! !
--- a/SignalError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/SignalError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,9 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
-
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#SignalError
@@ -49,5 +46,12 @@
 !SignalError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SignalError.st,v 1.5 2004-04-22 15:28:24 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/SignalError.st,v 1.5 2004/04/22 15:28:24 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: SignalError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/Smalltalk.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/Smalltalk.st	Thu Mar 28 12:21:50 2013 +0000
@@ -219,6 +219,7 @@
 "
 ! !
 
+
 !Smalltalk class methodsFor:'initialization'!
 
 basicInitializeSystem
@@ -383,9 +384,9 @@
     ObjectMemory recursionInterruptHandler:self.
 
     OperatingSystem isOSXlike ifTrue:[
-	"/ OSX sends SIGABRT for NSExceptions
-	OperatingSystem operatingSystemSignal:(OperatingSystem sigABRT) install:NSException.
-	OperatingSystem enableAbortInterrupts.
+        "/ OSX sends SIGABRT for NSExceptions
+        OperatingSystem operatingSystemSignal:(OperatingSystem sigABRT) install:NSException.
+        OperatingSystem enableAbortInterrupts.
     ].
 
     "
@@ -666,6 +667,7 @@
     Stdout reOpen. Stderr reOpen. Stdin reOpen.
 ! !
 
+
 !Smalltalk class methodsFor:'Compatibility-Squeak'!
 
 at:aKey ifAbsentPut:aBlock
@@ -798,6 +800,7 @@
     "
 ! !
 
+
 !Smalltalk class methodsFor:'Compatibility-V''Age'!
 
 allClassesImplementing:aSelector
@@ -832,6 +835,7 @@
     "Created: / 07-02-2012 / 15:57:05 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'Compatibility-VW5.4'!
 
 defineClass:nameSymbol superclass:superclass indexedType:indexed private:private instanceVariableNames:instVars classInstanceVariableNames:classInstVars imports:imports category:category
@@ -876,6 +880,7 @@
     ^ newNameSpace
 ! !
 
+
 !Smalltalk class methodsFor:'accessing'!
 
 associationAt:aKey
@@ -1184,6 +1189,7 @@
     "
 ! !
 
+
 !Smalltalk class methodsFor:'class management'!
 
 changeCategoryOf:aClass to:newCategory
@@ -1370,24 +1376,24 @@
     i2 := 1.
     ns := self.
     [i2 ~~ 0] whileTrue:[
-	i2 := newName indexOfSubCollection:'::' startingAt:i1.
-	i2 ~~ 0 ifTrue:[
-	    nm := newName copyFrom:i1 to:i2-1.
-	    ns isNameSpace ifTrue:[
-		subns := ns at:nm asSymbol ifAbsent:nil.
-		subns isNil ifTrue:[
-		    self error:'Nonexisting namespace: ',nm.
-		    ^ nil.
-		].
-	    ] ifFalse:[
-		subns := ns privateClassesAt:nm asSymbol.
-		subns isNil ifTrue:[
-		    self error:'Cannot create a namespace below a class'
-		]
-	    ].
-	    ns := subns.
-	    i1 := i2 + 2.
-	].
+        i2 := newName indexOfSubCollection:'::' startingAt:i1.
+        i2 ~~ 0 ifTrue:[
+            nm := newName copyFrom:i1 to:i2-1.
+            ns isNameSpace ifTrue:[
+                subns := ns at:nm asSymbol ifAbsent:nil.
+                subns isNil ifTrue:[
+                    self error:'Nonexisting namespace: ',nm.
+                    ^ nil.
+                ].
+            ] ifFalse:[
+                subns := ns privateClassesAt:nm asSymbol.
+                subns isNil ifTrue:[
+                    self error:'Cannot create a namespace below a class'
+                ]
+            ].
+            ns := subns.
+            i1 := i2 + 2.
+        ].
     ].
 
     oldName := aClass name.
@@ -1398,8 +1404,8 @@
     privateClasses := aClass privateClassesSorted.
 
     ((self at:oldSym) ~~ aClass) ifTrue:[
-	'Smalltalk [warning]: rename failed - name is different from key' errorPrintCR.
-	^ self
+        'Smalltalk [warning]: rename failed - name is different from key' errorPrintCR.
+        ^ self
     ].
 
     "/ rename the class
@@ -1408,42 +1414,42 @@
 
     "/ change the owning class
     ns isNameSpace ifFalse:[
-	aClass isPrivate ifTrue:[
-	    aClass class setOwningClass:ns.
-	] ifFalse:[
-	    "/ sigh - must make a PrivateMetaclass from Metaclass
-	    oldMetaclass := aClass class.
-	    newMetaclass := PrivateMetaclass new.
-	    newMetaclass flags:(oldMetaclass flags).
-	    newMetaclass setSuperclass:(oldMetaclass superclass).
-	    newMetaclass instSize:(oldMetaclass instSize).
-	    newMetaclass setInstanceVariableString:(oldMetaclass instanceVariableString).
-	    newMetaclass setMethodDictionary:(oldMetaclass methodDictionary).
-	    newMetaclass setSoleInstance:aClass.
-	    newMetaclass setOwningClass:ns.
-
-	    aClass changeClassTo:newMetaclass.
-	    ObjectMemory flushCaches.
-	]
+        aClass isPrivate ifTrue:[
+            aClass class setOwningClass:ns.
+        ] ifFalse:[
+            "/ sigh - must make a PrivateMetaclass from Metaclass
+            oldMetaclass := aClass class.
+            newMetaclass := PrivateMetaclass new.
+            newMetaclass flags:(oldMetaclass flags).
+            newMetaclass setSuperclass:(oldMetaclass superclass).
+            newMetaclass instSize:(oldMetaclass instSize).
+            newMetaclass setInstanceVariableString:(oldMetaclass instanceVariableString).
+            newMetaclass setMethodDictionary:(oldMetaclass methodDictionary).
+            newMetaclass setSoleInstance:aClass.
+            newMetaclass setOwningClass:ns.
+
+            aClass changeClassTo:newMetaclass.
+            ObjectMemory flushCaches.
+        ]
     ] ifTrue:[
-	aClass isPrivate ifTrue:[
-	    newCategory := aClass topOwningClass category.
-
-	    "/ sigh - must make a Metaclass from PrivateMetaclass
-	    oldMetaclass := aClass class.
-
-	    newMetaclass := Metaclass new.
-	    newMetaclass flags:(oldMetaclass flags).
-	    newMetaclass setSuperclass:(oldMetaclass superclass).
-	    newMetaclass instSize:(oldMetaclass instSize).
-	    newMetaclass setInstanceVariableString:(oldMetaclass instanceVariableString).
-	    newMetaclass setMethodDictionary:(oldMetaclass methodDictionary).
-	    newMetaclass setSoleInstance:aClass.
-
-	    aClass category:newCategory.
-	    aClass changeClassTo:newMetaclass.
-	    ObjectMemory flushCaches.
-	]
+        aClass isPrivate ifTrue:[
+            newCategory := aClass topOwningClass category.
+
+            "/ sigh - must make a Metaclass from PrivateMetaclass
+            oldMetaclass := aClass class.
+
+            newMetaclass := Metaclass new.
+            newMetaclass flags:(oldMetaclass flags).
+            newMetaclass setSuperclass:(oldMetaclass superclass).
+            newMetaclass instSize:(oldMetaclass instSize).
+            newMetaclass setInstanceVariableString:(oldMetaclass instanceVariableString).
+            newMetaclass setMethodDictionary:(oldMetaclass methodDictionary).
+            newMetaclass setSoleInstance:aClass.
+
+            aClass category:newCategory.
+            aClass changeClassTo:newMetaclass.
+            ObjectMemory flushCaches.
+        ]
     ].
 
     aClass setName:newSym.
@@ -1463,32 +1469,32 @@
 
     names := aClass classVariableString asCollectionOfWords.
     names do:[:name |
-	oldCVSym := (oldSym , ':' , name) asSymbol.
-	value := self at:oldCVSym.
-	self at:oldCVSym put:nil.
-
-	"/
-	"/ see comment in #removeKey: on why we dont remove it it here
-	"/
-	"/ self removeKey:cSym.
-
-	newCVSym := (newSym , ':' , name) asSymbol.
-	self at:newCVSym put:value.
-
-	oldNameToNewName at:oldCVSym put:newCVSym.
+        oldCVSym := (oldSym , ':' , name) asSymbol.
+        value := self at:oldCVSym.
+        self at:oldCVSym put:nil.
+
+        "/
+        "/ see comment in #removeKey: on why we dont remove it it here
+        "/
+        "/ self removeKey:cSym.
+
+        newCVSym := (newSym , ':' , name) asSymbol.
+        self at:newCVSym put:value.
+
+        oldNameToNewName at:oldCVSym put:newCVSym.
     ].
 
     "/ patch methods literal arrays from oldCVname to newCVname
 
     oldNameToNewName keysAndValuesDo:[:oldNameSym :newNameSym |
-	aClass withAllSubclasses do:[:aSubClass |
-	    Transcript showCR:'changing global accesses from ''' , oldNameSym , ''' into ''' , newNameSym , ''' in class: ''' , aSubClass name , ''' ...'.
-	    aSubClass instAndClassSelectorsAndMethodsDo:[:sel :aMethod |
-		aMethod changeLiteral:oldNameSym to:newNameSym
-	    ].
-	].
-
-	"/ and also in privateClasses ? ...
+        aClass withAllSubclasses do:[:aSubClass |
+            Transcript showCR:'changing global accesses from ''' , oldNameSym , ''' into ''' , newNameSym , ''' in class: ''' , aSubClass name , ''' ...'.
+            aSubClass instAndClassSelectorsAndMethodsDo:[:sel :aMethod |
+                aMethod changeLiteral:oldNameSym to:newNameSym
+            ].
+        ].
+
+        "/ and also in privateClasses ? ...
 
 "/        privateClasses size > 0 ifTrue:[
 "/            privateClasses do:[:aPrivateClass |
@@ -1511,85 +1517,85 @@
     newNameSpace := aClass topNameSpace.
 
     privateClasses size > 0 ifTrue:[
-	"/ must rename privateClasses as well
-	Class withoutUpdatingChangesDo:[
-	    privateClasses do:[:aPrivateClass |
-		self renameClass:aPrivateClass
-		     to:(newSym , '::' , aPrivateClass nameWithoutPrefix).
-
-		Transcript showCR:'recompiling methods in ''' , newNameSpace name , ''' accessing ''' , oldName , '::' , aPrivateClass nameWithoutPrefix , ''' ...'.
-		aClass theNonMetaclass recompileMethodsAccessingGlobal:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol.
-		aClass theMetaclass recompileMethodsAccessingGlobal:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol.
-		aClass theNonMetaclass recompileMethodsAccessingGlobal:(aPrivateClass nameWithoutPrefix) asSymbol.
-		aClass theMetaclass recompileMethodsAccessingGlobal:(aPrivateClass nameWithoutPrefix) asSymbol.
+        "/ must rename privateClasses as well
+        Class withoutUpdatingChangesDo:[
+            privateClasses do:[:aPrivateClass |
+                self renameClass:aPrivateClass
+                     to:(newSym , '::' , aPrivateClass nameWithoutPrefix).
+
+                Transcript showCR:'recompiling methods in ''' , newNameSpace name , ''' accessing ''' , oldName , '::' , aPrivateClass nameWithoutPrefix , ''' ...'.
+                aClass theNonMetaclass recompileMethodsAccessingGlobal:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol.
+                aClass theMetaclass recompileMethodsAccessingGlobal:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol.
+                aClass theNonMetaclass recompileMethodsAccessingGlobal:(aPrivateClass nameWithoutPrefix) asSymbol.
+                aClass theMetaclass recompileMethodsAccessingGlobal:(aPrivateClass nameWithoutPrefix) asSymbol.
 "/                ClassBuilder
 "/                    recompileGlobalAccessorsTo:(oldName , '::' , aPrivateClass nameWithoutPrefix) asSymbol
 "/                    in:newNameSpace
 "/                    except:nil.
-	    ]
-	]
+            ]
+        ]
     ].
 
     oldNameSpace ~~ newNameSpace ifTrue:[
 
-	"/ all those referencing the class from the old nameSpace
-	"/ must be recompiled ...
-	"/ (to now access the global from smalltalk)
-
-	oldNameSpace ~~ Smalltalk ifTrue:[
-	    Transcript showCR:'recompiling methods in ''' , oldNameSpace name , ''' accessing ''' , oldName , ''' ...'.
-
-	    ClassBuilder
-		recompileGlobalAccessorsTo:oldName asSymbol
-		in:oldNameSpace
-		except:nil.
-	].
-
-	"/ all referencing the class in the new namespace
-	"/ as well; to now access the new class.
-
-	(newNameSpace notNil and:[newNameSpace ~~ Smalltalk]) ifTrue:[
-	    Transcript showCR:'recompiling methods in ''' , newNameSpace name , ''' accessing ''' , oldBaseName , ''' ...'.
-
-	    ClassBuilder
-		recompileGlobalAccessorsTo:oldBaseName asSymbol
-		in:newNameSpace
-		except:nil.
-	].
+        "/ all those referencing the class from the old nameSpace
+        "/ must be recompiled ...
+        "/ (to now access the global from smalltalk)
+
+        oldNameSpace ~~ Smalltalk ifTrue:[
+            Transcript showCR:'recompiling methods in ''' , oldNameSpace name , ''' accessing ''' , oldName , ''' ...'.
+
+            ClassBuilder
+                recompileGlobalAccessorsTo:oldName asSymbol
+                in:oldNameSpace
+                except:nil.
+        ].
+
+        "/ all referencing the class in the new namespace
+        "/ as well; to now access the new class.
+
+        (newNameSpace notNil and:[newNameSpace ~~ Smalltalk]) ifTrue:[
+            Transcript showCR:'recompiling methods in ''' , newNameSpace name , ''' accessing ''' , oldBaseName , ''' ...'.
+
+            ClassBuilder
+                recompileGlobalAccessorsTo:oldBaseName asSymbol
+                in:newNameSpace
+                except:nil.
+        ].
     ] ifFalse:[
-	"/ all references to a global with my new name in my owning class
-	"/ must now be redirected to myself.
-
-	aClass isPrivate ifTrue:[
-	    newBaseName := aClass nameWithoutNameSpacePrefix.
-	    newBaseNameWithoutPrefix := aClass nameWithoutPrefix.
-
-	    Transcript showCR:'recompiling methods accessing ''' , oldBaseNameWithoutPrefix , ''' in: ''' , aClass owningClass name , ''' ...'.
-	    aClass owningClass recompileMethodsAccessingGlobal:oldBaseNameWithoutPrefix.
-	    aClass owningClass class recompileMethodsAccessingGlobal:oldBaseNameWithoutPrefix.
-
-	    Transcript showCR:'recompiling methods accessing ''' , oldBaseName , ''' in: ''' , aClass owningClass name , ''' ...'.
-	    aClass owningClass recompileMethodsAccessingGlobal:oldBaseName.
-	    aClass owningClass class recompileMethodsAccessingGlobal:oldBaseName.
-
-	    Transcript showCR:'recompiling methods accessing ''' , newBaseNameWithoutPrefix , ''' in: ''' , aClass owningClass name , ''' ...'.
-	    aClass owningClass recompileMethodsAccessingGlobal:newBaseNameWithoutPrefix.
-	    aClass owningClass class recompileMethodsAccessingGlobal:newBaseNameWithoutPrefix.
-
-	    Transcript showCR:'recompiling methods accessing ''' , newBaseName , ''' in: ''' , aClass owningClass name , ''' ...'.
-	    aClass owningClass recompileMethodsAccessingGlobal:newBaseName.
-	    aClass owningClass class recompileMethodsAccessingGlobal:newBaseName.
-	]
+        "/ all references to a global with my new name in my owning class
+        "/ must now be redirected to myself.
+
+        aClass isPrivate ifTrue:[
+            newBaseName := aClass nameWithoutNameSpacePrefix.
+            newBaseNameWithoutPrefix := aClass nameWithoutPrefix.
+
+            Transcript showCR:'recompiling methods accessing ''' , oldBaseNameWithoutPrefix , ''' in: ''' , aClass owningClass name , ''' ...'.
+            aClass owningClass recompileMethodsAccessingGlobal:oldBaseNameWithoutPrefix.
+            aClass owningClass class recompileMethodsAccessingGlobal:oldBaseNameWithoutPrefix.
+
+            Transcript showCR:'recompiling methods accessing ''' , oldBaseName , ''' in: ''' , aClass owningClass name , ''' ...'.
+            aClass owningClass recompileMethodsAccessingGlobal:oldBaseName.
+            aClass owningClass class recompileMethodsAccessingGlobal:oldBaseName.
+
+            Transcript showCR:'recompiling methods accessing ''' , newBaseNameWithoutPrefix , ''' in: ''' , aClass owningClass name , ''' ...'.
+            aClass owningClass recompileMethodsAccessingGlobal:newBaseNameWithoutPrefix.
+            aClass owningClass class recompileMethodsAccessingGlobal:newBaseNameWithoutPrefix.
+
+            Transcript showCR:'recompiling methods accessing ''' , newBaseName , ''' in: ''' , aClass owningClass name , ''' ...'.
+            aClass owningClass recompileMethodsAccessingGlobal:newBaseName.
+            aClass owningClass class recompileMethodsAccessingGlobal:newBaseName.
+        ]
     ].
 
     aClass changed:#definition.
     "/ because of the change of my superclasses name ...
     aClass allSubclassesDo:[:subClass |
-	subClass changed:#definition.
+        subClass changed:#definition.
     ].
     "/ because of the change of my superclasses name ...
     aClass subclassesDo:[:subClass |
-	subClass addChangeRecordForClass:subClass.
+        subClass addChangeRecordForClass:subClass.
     ].
     self changed:#definition.
     self changed:#classRename with:(Array with:aClass with:oldName).
@@ -1599,6 +1605,7 @@
     "Modified: / 05-09-2006 / 12:52:25 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'copying'!
 
 deepCopy
@@ -1634,6 +1641,7 @@
     "Modified: 18.5.1996 / 12:13:42 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'debugging ST/X'!
 
 compileTrace:aBoolean
@@ -1744,6 +1752,7 @@
     "Modified: / 19-01-2012 / 10:15:35 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'enumerating'!
 
 allBehaviorsDo:aBlock
@@ -2085,6 +2094,7 @@
     ]
 ! !
 
+
 !Smalltalk class methodsFor:'message control'!
 
 silentLoading
@@ -2120,6 +2130,7 @@
     aBlock ensure:[ SilentLoading := sav ].
 ! !
 
+
 !Smalltalk class methodsFor:'misc accessing'!
 
 beHeadless:aBoolean
@@ -2142,6 +2153,7 @@
     StandAlone := aBoolean
 ! !
 
+
 !Smalltalk class methodsFor:'private-system management-packages'!
 
 knownPackages
@@ -2183,7 +2195,9 @@
     "
      if there is a sourceCodeManager, ask it first for the extensions
     "
-    mgr := Smalltalk at:#SourceCodeManager.
+    (Smalltalk at:#AbstractSourceCodeManager) notNil ifTrue:[
+	mgr := AbstractSourceCodeManager managerForPackage: aPackageId
+    ].
     mgr notNil ifTrue:[
 	extensionsFilename := 'extensions.' , language sourceFileSuffix.
 
@@ -2195,7 +2209,21 @@
 	    extensionsRevisionString notNil ifTrue:[
 		extensionsRevisionInfo := mgr revisionInfoFromString:extensionsRevisionString inClass:nil.
 		extensionsRevisionInfo notNil ifTrue:[
-		    extensionsRevisionInfo fileName = extensionsFilename ifFalse:[^ false].
+		    extensionsRevisionInfo fileName = extensionsFilename ifFalse:[
+			"JV@2011-10-23: following condition is never satisfied for
+			 filed-in packages. The whole scheme of extensionVersion_XXX
+			 works ONLY for compiled packages as it depends on fact, that
+			 extension Init() routine is called AFTER all classes are inited,
+			 therefore the extensionVersion_XXX methods from extensions.st
+			 overwrites methods coming from package definition class. All this
+			 is so tricky and error prone, that we have to come up with better
+			 solution!!"
+			packageDirName notNil ifTrue:[
+			    ^ self loadExtensionsFromDirectory:packageDirName language: language
+			] ifFalse:[
+			    ^ false
+			]
+		    ]
 		]
 	    ].
 	    SourceCodeManagerError handle:[:ex |
@@ -2229,6 +2257,7 @@
     "Created: / 02-01-2010 / 10:41:47 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 19-03-2011 / 10:03:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 04-11-2011 / 13:41:29 / cg"
+    "Modified: / 23-10-2011 / 19:35:18 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 loadExtensionsFromDirectory:packageDirOrString
@@ -2250,18 +2279,19 @@
 
     f := packageDir / ('extensions.' , language sourceFileSuffix).
     f exists ifTrue:[
-	Class withoutUpdatingChangeSetDo:[
-	    f fileIn.
-	].
-	VerboseLoading ifTrue:[
-	    Transcript showCR:('loaded extensions: ' , f pathName).
-	].
-	^ true
-    ].
-    ^ false
+        Class withoutUpdatingChangeSetDo:[
+            f fileIn.
+        ].
+        VerboseLoading ifTrue:[
+            Transcript showCR:('loaded extensions: ' , f pathName).
+        ].
+        ^ true
+    ].
+    ^ true"/false
 
     "Created: / 02-01-2010 / 10:38:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
     "Modified: / 04-11-2011 / 13:41:19 / cg"
+    "Modified: / 31-01-2013 / 11:33:48 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 loadPackage:aPackageStringArg asAutoloaded:doLoadAsAutoloaded
@@ -2279,28 +2309,28 @@
     "/ if there is a projectDefinition, let it load itself...
     def := packageId projectDefinitionClass.
     (def notNil and:[def isLoaded]) ifTrue:[
-	def loadAsAutoloaded:doLoadAsAutoloaded.
-	^ true.
+        def loadAsAutoloaded:doLoadAsAutoloaded.
+        ^ true.
     ].
 
     packageDir := self packageDirectoryForPackageId:packageId.
     packageDir isNil ifTrue:[
-	(packageString includes:$:) ifFalse:[
-	    "/ assume stx
-	    packageDir := self packageDirectoryForPackageId:('stx:',packageString).
-	].
+        (packageString includes:$:) ifFalse:[
+            "/ assume stx
+            packageDir := self packageDirectoryForPackageId:('stx:',packageString).
+        ].
     ].
 
     (self
-	loadPackage:packageString
-	fromDirectory:packageDir
-	asAutoloaded:doLoadAsAutoloaded) ifTrue: [^ true].
+        loadPackage:packageString
+        fromDirectory:packageDir
+        asAutoloaded:doLoadAsAutoloaded) ifTrue: [^ true].
 
     AbstractSourceCodeManager notNil ifTrue:[
-	sourceCodeManager := AbstractSourceCodeManager sourceCodeManagerForPackage: packageString.
-	sourceCodeManager notNil ifTrue:[
-	    ^ sourceCodeManager loadPackageWithId: packageString fromRepositoryAsAutoloaded: doLoadAsAutoloaded
-	].
+        sourceCodeManager := AbstractSourceCodeManager sourceCodeManagerForPackage: packageString.
+        sourceCodeManager notNil ifTrue:[
+            ^ sourceCodeManager loadPackageWithId: packageString fromRepositoryAsAutoloaded: doLoadAsAutoloaded
+        ].
     ].
 
     ^ false
@@ -2412,12 +2442,12 @@
      loadOK loadErrorOccurred exePath|
 
     packageDirOrStringOrNil notNil ifTrue:[
-	packageDir := packageDirOrStringOrNil asFilename.
+        packageDir := packageDirOrStringOrNil asFilename.
     ].
     VerboseLoading ifTrue:[
-	silent := false
+        silent := false
     ] ifFalse:[
-	silent := (SilentLoading or:[ StandAlone ]) or:[ InfoPrinting not ].
+        silent := (SilentLoading or:[ StandAlone ]) or:[ InfoPrinting not ].
     ].
 
     "For now: have to read the project definition first!!
@@ -2431,31 +2461,31 @@
 false ifTrue:[
     "if not, file it in ..."
     (projectDefinitionClass isNil and:[packageDir notNil]) ifTrue:[
-	projectDefinitionClassName := ProjectDefinition initialClassNameForDefinitionOf:aPackageString.
-	"/ try to load the project definition class
-	projectDefinitionFilename := (packageDir / projectDefinitionClassName) withSuffix:'st'.
-	projectDefinitionFilename exists ifFalse:[
-	    projectDefinitionFilename := (packageDir / 'source' / projectDefinitionClassName) withSuffix:'st'.
-	].
-	projectDefinitionFilename exists ifTrue:[
-	    Class withoutUpdatingChangesDo:[
-		Smalltalk silentlyLoadingDo:[
-		    projectDefinitionFilename fileIn.
-		].
-	    ].
-	    projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
-	    projectDefinitionClass notNil ifTrue:[
-		projectDefinitionClass loadDirectory:(projectDefinitionFilename asFilename directory)
-	    ]
-	].
+        projectDefinitionClassName := ProjectDefinition initialClassNameForDefinitionOf:aPackageString.
+        "/ try to load the project definition class
+        projectDefinitionFilename := (packageDir / projectDefinitionClassName) withSuffix:'st'.
+        projectDefinitionFilename exists ifFalse:[
+            projectDefinitionFilename := (packageDir / 'source' / projectDefinitionClassName) withSuffix:'st'.
+        ].
+        projectDefinitionFilename exists ifTrue:[
+            Class withoutUpdatingChangesDo:[
+                Smalltalk silentlyLoadingDo:[
+                    projectDefinitionFilename fileIn.
+                ].
+            ].
+            projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
+            projectDefinitionClass notNil ifTrue:[
+                projectDefinitionClass loadDirectory:(projectDefinitionFilename asFilename directory)
+            ]
+        ].
     ].
     projectDefinitionClass notNil ifTrue:[
-	projectDefinitionClass autoload.
-	somethingHasBeenLoaded := projectDefinitionClass loadAsAutoloaded:doLoadAsAutoloaded.
-	(silent not and:[somethingHasBeenLoaded]) ifTrue:[
-	    Transcript showCR:('Smalltalk [info]: loaded package: ' , aPackageString , ' from project definition').
-	].
-	^ true.
+        projectDefinitionClass autoload.
+        somethingHasBeenLoaded := projectDefinitionClass loadAsAutoloaded:doLoadAsAutoloaded.
+        (silent not and:[somethingHasBeenLoaded]) ifTrue:[
+            Transcript showCR:('Smalltalk [info]: loaded package: ' , aPackageString , ' from project definition').
+        ].
+        ^ true.
     ].
 ].
 
@@ -2463,7 +2493,7 @@
 
     "Is there a shared library (.dll or .so) ?"
     shLibName := aPackageString asPackageId libraryName asFilename
-			withSuffix:ObjectFileLoader sharedLibrarySuffix.
+                        withSuffix:ObjectFileLoader sharedLibrarySuffix.
 
 "/    silent ifFalse:[
 "/        Transcript showCR:('looking for binary classLib file: ' , shLibName pathName).
@@ -2471,117 +2501,117 @@
     exePath := OperatingSystem pathOfSTXExecutable asFilename directory.
     binaryClassLibraryFilename := exePath / shLibName.
     binaryClassLibraryFilename exists ifFalse:[
-	exePath baseName = 'bin' ifTrue:[
-	    binaryClassLibraryFilename := exePath directory / 'lib' / shLibName.
-	].
-	binaryClassLibraryFilename exists ifFalse:[
-	    binaryClassLibraryFilename := exePath directory / 'plugin' / shLibName.
-	    binaryClassLibraryFilename exists ifFalse:[
+        exePath baseName = 'bin' ifTrue:[
+            binaryClassLibraryFilename := exePath directory / 'lib' / shLibName.
+        ].
+        binaryClassLibraryFilename exists ifFalse:[
+            binaryClassLibraryFilename := exePath directory / 'plugin' / shLibName.
+            binaryClassLibraryFilename exists ifFalse:[
 "/                binaryClassLibraryFilename := Filename currentDirectory / shLibName.
 "/                binaryClassLibraryFilename exists ifFalse:[
-		    packageDir notNil ifTrue:[
-			binaryClassLibraryFilename := packageDir / shLibName.
-			binaryClassLibraryFilename exists ifFalse:[
-			    "/ mhmh - is this a good idea ? (temporary kludge)
-			    ExternalAddress pointerSize == 4 ifTrue:[
-				binaryClassLibraryFilename := packageDir / 'objbc' / shLibName.
-				binaryClassLibraryFilename exists ifFalse:[
-				    binaryClassLibraryFilename := packageDir / 'objvc' / shLibName.
-				]
-			    ] ifFalse:[
-				binaryClassLibraryFilename := packageDir / 'objmingw' / shLibName.
-			    ].
-			]
-		    ]
+                    packageDir notNil ifTrue:[
+                        binaryClassLibraryFilename := packageDir / shLibName.
+                        binaryClassLibraryFilename exists ifFalse:[
+                            "/ mhmh - is this a good idea ? (temporary kludge)
+                            ExternalAddress pointerSize == 4 ifTrue:[    
+                                binaryClassLibraryFilename := packageDir / 'objbc' / shLibName.
+                                binaryClassLibraryFilename exists ifFalse:[
+                                    binaryClassLibraryFilename := packageDir / 'objvc' / shLibName.
+                                ]
+                            ] ifFalse:[
+                                binaryClassLibraryFilename := packageDir / 'objmingw' / shLibName.
+                            ].
+                        ]
+                    ]
 "/                ].
-	    ].
-	].
-	packageDir notNil ifTrue:[
-	    binaryClassLibraryFilename exists ifFalse:[
-		"/ look in package directory
-		binaryClassLibraryFilename := packageDir / shLibName.
-		binaryClassLibraryFilename exists ifFalse:[
-		    ExternalAddress pointerSize == 4 ifTrue:[
-			binaryClassLibraryFilename := packageDir / 'objbc' / shLibName.
-			binaryClassLibraryFilename exists ifFalse:[
-			    binaryClassLibraryFilename := packageDir / 'objvc' / shLibName.
-			]
-		    ] ifFalse:[
-			binaryClassLibraryFilename := packageDir / 'objmingw' / shLibName.
-		    ].
-		].
-	    ].
-	].
+            ].
+        ].
+        packageDir notNil ifTrue:[
+            binaryClassLibraryFilename exists ifFalse:[
+                "/ look in package directory
+                binaryClassLibraryFilename := packageDir / shLibName.
+                binaryClassLibraryFilename exists ifFalse:[
+                    ExternalAddress pointerSize == 4 ifTrue:[    
+                        binaryClassLibraryFilename := packageDir / 'objbc' / shLibName.
+                        binaryClassLibraryFilename exists ifFalse:[
+                            binaryClassLibraryFilename := packageDir / 'objvc' / shLibName.
+                        ]
+                    ] ifFalse:[
+                        binaryClassLibraryFilename := packageDir / 'objmingw' / shLibName.
+                    ].
+                ].
+            ].
+        ].
     ].
 
     binaryClassLibraryFilename exists ifTrue:[
-	ObjectFileLoader::ObjectFileLoadErrorNotification handle:[:ex |
-	    loadErrorOccurred := true.
-	    ex proceedWith:true.
-	] do:[
-	    loadOK := (ObjectFileLoader loadObjectFile:binaryClassLibraryFilename) notNil.
-	    "/ loadOK := self loadPackage:aPackageString fromClassLibrary:binaryClassLibraryFilename.
-	].
-	loadOK ifTrue:[
-	    silent ifFalse:[
-		Transcript showCR:('loaded package: ' , aPackageString , ' from binary classLib file: ' , binaryClassLibraryFilename pathName).
-	    ].
-	    "now, all compiled classes have been loaded.
-	     keep classes in the package which are autoloaded as autoloaded.
-	     (so the code below is disabled)"
+        ObjectFileLoader::ObjectFileLoadErrorNotification handle:[:ex |
+            loadErrorOccurred := true.
+            ex proceedWith:true.
+        ] do:[
+            loadOK := (ObjectFileLoader loadObjectFile:binaryClassLibraryFilename) notNil.
+            "/ loadOK := self loadPackage:aPackageString fromClassLibrary:binaryClassLibraryFilename.
+        ].
+        loadOK ifTrue:[
+            silent ifFalse:[
+                Transcript showCR:('loaded package: ' , aPackageString , ' from binary classLib file: ' , binaryClassLibraryFilename pathName).
+            ].
+            "now, all compiled classes have been loaded.
+             keep classes in the package which are autoloaded as autoloaded.
+             (so the code below is disabled)"
 "/            doLoadAsAutoloaded ifFalse:[
 "/                "/ force autoloading...
 "/                Smalltalk allClassesDo:[:eachClass |
 "/                    eachClass package == aPackageString ifTrue:[eachClass autoload].
 "/                ].
 "/            ].
-	    ^ true
-	].
-	loadErrorOccurred ifTrue:[
-	    self breakPoint:#cg.
-	    projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
-	    projectDefinitionClass notNil ifTrue:[
-		"/ load prerequisites...
-		projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
-		self breakPoint:#cg.
-	    ].
-	].
+            ^ true
+        ].
+        loadErrorOccurred ifTrue:[
+            self breakPoint:#cg.
+            projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
+            projectDefinitionClass notNil ifTrue:[
+                "/ load prerequisites...
+                projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
+                self breakPoint:#cg.
+            ].
+        ].
     ].
 
     packageDir isNil ifTrue:[
-	^ false.
+        ^ false.
     ].
 
     "fallback - go through the project definition"
     projectDefinitionClass isNil ifTrue:[
-	projectDefinitionClassName := ProjectDefinition initialClassNameForDefinitionOf:aPackageString.
-	"/ try to load the project definition class
-	projectDefinitionFilename := (packageDir / projectDefinitionClassName) withSuffix:'st'.
-	projectDefinitionFilename exists ifFalse:[
-	    projectDefinitionFilename := (packageDir / 'source' / projectDefinitionClassName) withSuffix:'st'.
-	].
-	projectDefinitionFilename exists ifTrue:[
-	    Class withoutUpdatingChangesDo:[
-		Smalltalk silentlyLoadingDo:[
-		    projectDefinitionFilename fileIn.
-		].
-	    ].
-	    projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
+        projectDefinitionClassName := ProjectDefinition initialClassNameForDefinitionOf:aPackageString.
+        "/ try to load the project definition class
+        projectDefinitionFilename := (packageDir / projectDefinitionClassName) withSuffix:'st'.
+        projectDefinitionFilename exists ifFalse:[
+            projectDefinitionFilename := (packageDir / 'source' / projectDefinitionClassName) withSuffix:'st'.
+        ].
+        projectDefinitionFilename exists ifTrue:[
+            Class withoutUpdatingChangesDo:[
+                Smalltalk silentlyLoadingDo:[
+                    projectDefinitionFilename fileIn.
+                ].
+            ].
+            projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
 "/ done below
 "/            projectDefinitionClass notNil ifTrue:[
 "/                projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
 "/                projectDefinitionClass loadDirectory:(projectDefinitionFilename asFilename directory)
 "/            ]
-	].
+        ].
     ].
     projectDefinitionClass notNil ifTrue:[
-	projectDefinitionClass autoload.
-	projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
-	somethingHasBeenLoaded := projectDefinitionClass loadAsAutoloaded:doLoadAsAutoloaded.
-	(silent not and:[somethingHasBeenLoaded]) ifTrue:[
-	    Transcript showCR:('Smalltalk [info]: loaded package: ' , aPackageString , ' from project definition').
-	].
-	^ true.
+        projectDefinitionClass autoload.
+        projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
+        somethingHasBeenLoaded := projectDefinitionClass loadAsAutoloaded:doLoadAsAutoloaded.
+        (silent not and:[somethingHasBeenLoaded]) ifTrue:[
+            Transcript showCR:('Smalltalk [info]: loaded package: ' , aPackageString , ' from project definition').
+        ].
+        ^ true.
     ].
 
 "/ loadAll no longer supported
@@ -2640,14 +2670,14 @@
     "/ source files-file loading no longer supported
     "/ however, allow for autoload-stub loaded
     doLoadAsAutoloaded ifTrue:[
-	self
-	    recursiveInstallAutoloadedClassesFrom:packageDir
-	    rememberIn:(Set new)
-	    maxLevels:2
-	    noAutoload:false
-	    packageTop:packageDir
-	    showSplashInLevels:0.
-	^ true
+        self
+            recursiveInstallAutoloadedClassesFrom:packageDir
+            rememberIn:(Set new)
+            maxLevels:2
+            noAutoload:false
+            packageTop:packageDir
+            showSplashInLevels:0.
+        ^ true
     ].
 
 "/    doLoadAsAutoloaded ifFalse:[
@@ -2738,6 +2768,7 @@
     "Modified: / 04-11-2011 / 13:43:29 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'queries'!
 
 allClasses
@@ -2833,7 +2864,7 @@
 
     methods := OrderedCollection new.
     self allClassesDo:[:eachClass |
-	methods addAll:(eachClass extensionsFrom:aProjectID).
+        methods addAll:(eachClass extensionsFrom:aProjectID).
     ].
     ^ methods
 !
@@ -3399,6 +3430,7 @@
     "Modified: / 14.6.1998 / 15:54:03 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'queries-system'!
 
 dialectName
@@ -3473,6 +3505,7 @@
     ^ false
 ! !
 
+
 !Smalltalk class methodsFor:'startup'!
 
 browserWindowStartup
@@ -4062,186 +4095,189 @@
     Initializing := true.
 
     (StartupClass perform:#keepSplashWindowOpen ifNotUnderstood:[false]) ifFalse:[
-	self hideSplashWindow.   "/ if there is one, it's now time to hide it
+        self hideSplashWindow.   "/ if there is one, it's now time to hide it
     ].
 
     "
      while reading patches- and rc-file, do not add things into change-file
     "
     Class withoutUpdatingChangesDo:[
-	|commandFile defaultRC prevCatchSetting|
-
-	didReadRCFile := false.
-
-	StandAlone ifFalse:[
-	    "/
-	    "/ look for any '-q', '-e' or '-f' command line arguments
-	    "/ and handle them;
-	    "/ read startup and patches file
-	    "/
-	    idx := CommandLineArguments indexOf:'-q'.
-	    idx == 0 ifTrue:[
-		idx := CommandLineArguments indexOf:'--silent'.
-	    ].
-	    idx ~~ 0 ifTrue:[
-		Object infoPrinting:false.
-		ObjectMemory infoPrinting:false.
-		CommandLineArguments removeAtIndex:idx.
-	    ].
-
-	    "/ look for a '--repl' argument
-	    "/ then go into a read-eval-print loop immediately
-	    idx := CommandLineArguments indexOf:'--repl'.
-	    idx ~~ 0 ifTrue:[
-		CommandLineArguments removeAtIndex:idx.
-		self startSchedulerAndBackgroundCollector.
-		self readEvalPrint.
-		self exit.
-	    ].
-
-	    "/ look for a '-e filename' or '--execute filename' argument
-	    "/ this will force fileIn of filename only, no standard startup.
-
-	    idx := CommandLineArguments indexOf:'-e'.
-	    idx == 0 ifTrue:[
-		idx := CommandLineArguments indexOf:'--execute'.
-		idx == 0 ifTrue:[
-		    idx := CommandLineArguments indexOf:'--script'.
-		    idx ~~ 0 ifTrue:[
-			SilentLoading := true.
-		    ].
-		].
-	    ].
-	    idx ~~ 0 ifTrue:[
-		|process|
-
-		CommandName := arg := CommandLineArguments at:idx + 1.
-
-		CommandLineArguments
-		    removeAtIndex:idx+1; removeAtIndex:idx.
-
-		self startSchedulerAndBackgroundCollector.
-		Initializing := false.
-
-		process := [
-		    arg = '-' ifTrue:[
-			self fileInStream:Stdin
-			       lazy:nil
-			       silent:nil
-			       logged:false
-			       addPath:nil
-		    ] ifFalse:[
-			IsSTScript := true.
-			self fileIn:arg.
-		    ].
-		    self exit.
-		] newProcess.
-		process priority:(Processor userSchedulingPriority).
-		process name:'main'.
-		process beGroupLeader.
-		process resume.
-
-		Processor dispatchLoop.
-		self exit
-	    ].
-
-	    "/ look for a '-E expr' or '--eval expr' argument
-	    "/ this will force evaluation of expr only, no standard startup
-	    idx := CommandLineArguments indexOf:'-E'.
-	    idx == 0 ifTrue:[
-		idx := CommandLineArguments indexOf:'--eval'.
-	    ].
-	    idx ~~ 0 ifTrue:[
-		arg := CommandLineArguments at:idx + 1.
-
-		CommandLineArguments
-		    removeAtIndex:idx+1; removeAtIndex:idx.
-
-		self startSchedulerAndBackgroundCollector.
-		Initializing := false.
-
-		self
-		    fileInStream:arg readStream
-		    lazy:nil
-		    silent:nil
-		    logged:false
-		    addPath:nil.
-
-		self exit
-	    ].
-
-	    "look for a '-f filename' or '--file filename' argument
-	     this will force evaluation of filename instead of smalltalk.rc"
-
-	    idx := CommandLineArguments indexOf:'-f'.
-	    idx == 0 ifTrue:[
-		idx := CommandLineArguments indexOf:'--file'.
-	    ].
-	    idx ~~ 0 ifTrue:[
-		CommandName := commandFile := CommandLineArguments at:idx+1.
-		CommandLineArguments removeAtIndex:idx+1; removeAtIndex:idx.
-	    ].
-	].
-
-	commandFile notNil ifTrue:[
-	    self startSchedulerAndBackgroundCollector.
-	    Initializing := false.
-
-	    (self secureFileIn:commandFile) ifFalse:[
-		('Smalltalk [error]: startup file "', commandFile, '" not found.') errorPrintCR.
-		OperatingSystem exit:1.
-	    ].
-	] ifFalse:[
-	    "/ look for <command>.rc
-	    "/ if not found, read smalltalk.rc (or stxapp.rc for standAlone operation)
-
-	    commandFile := self commandName asFilename withSuffix:'rc'.
-	    (didReadRCFile := commandFile exists and:[self secureFileIn:commandFile]) ifFalse:[
-		StandAlone ifFalse:[
-		    defaultRC := 'smalltalk.rc' asFilename
-		] ifTrue:[
-		    defaultRC := 'stxapp.rc' asFilename
-		].
-
-		didReadRCFile := defaultRC exists and:[self secureFileIn:defaultRC].
-		didReadRCFile ifFalse:[
-		    StandAlone ifFalse:[
-			'Smalltalk [warning]: no startup rc-file found. Going into line-by-line interpreter.' infoPrintCR.
-			graphicalMode := false.
-		    ]
-		]
-	    ].
-
-	    "/ ('StandAlone is %1' bindWith:StandAlone) printCR.
-	    "/ ('Headless is %1' bindWith:HeadlessOperation) printCR.
-	    "/ ('Display is %1' bindWith:Display) printCR.
-	    "/ ('Screen is %1' bindWith:Screen) printCR.
-
-	    didReadRCFile ifFalse:[
-		'private.rc' asFilename exists ifTrue:[ self secureFileIn:'private.rc' ].
-
-		"/
-		"/ No RC file found;
-		"/ Setup more default stuff
-		"/
-		StandAlone ifFalse:[
-		    "/ its a smalltalk - proceed in interpreter.
-		    'Smalltalk [warning]: no startup rc-file found. Going into line-by-line interpreter.' infoPrintCR.
-		    graphicalMode := false.
-		].
-
-		"/ setup more defaults...
+        |commandFile defaultRC prevCatchSetting|
+
+        didReadRCFile := false.
+
+        StandAlone ifFalse:[
+            "/
+            "/ look for any '-q', '-e' or '-f' command line arguments
+            "/ and handle them;
+            "/ read startup and patches file
+            "/
+            idx := CommandLineArguments indexOf:'-q'.
+            idx == 0 ifTrue:[
+                idx := CommandLineArguments indexOf:'--silent'.
+            ].
+            idx ~~ 0 ifTrue:[
+                Object infoPrinting:false.
+                ObjectMemory infoPrinting:false.
+                CommandLineArguments removeAtIndex:idx.
+            ].
+
+            "/ look for a '--repl' argument
+            "/ then go into a read-eval-print loop immediately
+            idx := CommandLineArguments indexOf:'--repl'.
+            idx ~~ 0 ifTrue:[
+                CommandLineArguments removeAtIndex:idx.
+                self startSchedulerAndBackgroundCollector.
+                self readEvalPrint.
+                self exit.
+            ].
+
+            "/ look for a '-e filename' or '--execute filename' argument
+            "/ this will force fileIn of filename only, no standard startup.
+
+            idx := CommandLineArguments indexOf:'-e'.
+            idx == 0 ifTrue:[
+                idx := CommandLineArguments indexOf:'--execute'.
+                idx == 0 ifTrue:[
+                    idx := CommandLineArguments indexOf:'--script'.
+                    idx ~~ 0 ifTrue:[
+                        SilentLoading := true.
+                    ].
+                ].
+            ].
+            idx ~~ 0 ifTrue:[
+                |process|
+
+                CommandName := arg := CommandLineArguments at:idx + 1.
+
+                CommandLineArguments
+                    removeAtIndex:idx+1; removeAtIndex:idx.
+
+                self startSchedulerAndBackgroundCollector.
+                Initializing := false.
+
+                process := [
+                    arg = '-' ifTrue:[
+                        self fileInStream:Stdin
+                               lazy:nil
+                               silent:nil
+                               logged:false
+                               addPath:nil
+                    ] ifFalse:[
+                        IsSTScript := true.
+                        self fileIn:arg.
+                    ].
+                    self exit.
+                ] newProcess.
+                process priority:(Processor userSchedulingPriority).
+                process name:'main'.
+                process beGroupLeader.
+                process resume.
+
+                Processor dispatchLoop.
+                self exit
+            ].
+
+            "/ look for a '-E expr' or '--eval expr' argument
+            "/ this will force evaluation of expr only, no standard startup
+            idx := CommandLineArguments indexOf:'-E'.
+            idx == 0 ifTrue:[
+                idx := CommandLineArguments indexOf:'--eval'.
+            ].
+            idx ~~ 0 ifTrue:[
+                arg := CommandLineArguments at:idx + 1.
+
+                CommandLineArguments
+                    removeAtIndex:idx+1; removeAtIndex:idx.
+
+                self startSchedulerAndBackgroundCollector.
+                Initializing := false.
+
+                self
+                    fileInStream:arg readStream
+                    lazy:nil
+                    silent:nil
+                    logged:false
+                    addPath:nil.
+
+                self exit
+            ].
+
+            "look for a '-f filename' or '--file filename' argument
+             this will force evaluation of filename instead of smalltalk.rc"
+
+            idx := CommandLineArguments indexOf:'-f'.
+            idx == 0 ifTrue:[
+                idx := CommandLineArguments indexOf:'--file'.
+            ].
+            idx ~~ 0 ifTrue:[
+                CommandName := commandFile := CommandLineArguments at:idx+1.
+                CommandLineArguments removeAtIndex:idx+1; removeAtIndex:idx.
+            ].
+        ].
+
+        commandFile notNil ifTrue:[
+            self startSchedulerAndBackgroundCollector.
+            Initializing := false.
+
+            (self secureFileIn:commandFile) ifFalse:[
+                ('Smalltalk [error]: startup file "', commandFile, '" not found.') errorPrintCR.
+                OperatingSystem exit:1.
+            ].
+        ] ifFalse:[
+            "/ look for <command>.rc
+            "/ if not found, read smalltalk.rc (or stxapp.rc for standAlone operation)
+
+            commandFile := self commandName asFilename withSuffix:'rc'.
+            (didReadRCFile := commandFile exists and:[self secureFileIn:commandFile]) ifFalse:[
+                StandAlone ifFalse:[
+                    defaultRC := 'smalltalk.rc' "/asFilename
+                ] ifTrue:[
+                    defaultRC := 'stxapp.rc' "/asFilename
+                ].
+                "JV@2011-11-01: DO NOT check defaultRC exist - this prevents smalltalk to
+                    to be started with different working directory than stx/projects/smalltalk !!!!!!"
+
+                "/didReadRCFile := defaultRC exists and:[self secureFileIn:defaultRC].
+                didReadRCFile := self secureFileIn:defaultRC.
+                didReadRCFile ifFalse:[
+                    StandAlone ifFalse:[
+                        'Smalltalk [warning]: no startup rc-file found. Going into line-by-line interpreter.' infoPrintCR.
+                        graphicalMode := false.
+                    ]
+                ]
+            ].
+
+            "/ ('StandAlone is %1' bindWith:StandAlone) printCR.
+            "/ ('Headless is %1' bindWith:HeadlessOperation) printCR.
+            "/ ('Display is %1' bindWith:Display) printCR.
+            "/ ('Screen is %1' bindWith:Screen) printCR.
+
+            didReadRCFile ifFalse:[
+                'private.rc' asFilename exists ifTrue:[ self secureFileIn:'private.rc' ].
+
+                "/
+                "/ No RC file found;
+                "/ Setup more default stuff
+                "/
+                StandAlone ifFalse:[
+                    "/ its a smalltalk - proceed in interpreter.
+                    'Smalltalk [warning]: no startup rc-file found. Going into line-by-line interpreter.' infoPrintCR.
+                    graphicalMode := false.
+                ].
+
+                "/ setup more defaults...
 "/                ObjectMemory startBackgroundCollectorAt:5.
 "/                ObjectMemory startBackgroundFinalizationAt:5.
-		self addStartBlock:[
-		    self startSchedulerAndBackgroundCollector
-		].
-	    ].
-	].
+                self addStartBlock:[
+                    self startSchedulerAndBackgroundCollector
+                ].
+            ].
+        ].
     ].
 
     HeadlessOperation ifTrue:[
-	graphicalMode := false.
+        graphicalMode := false.
     ].
 
     self mainStartup:graphicalMode
@@ -4281,6 +4317,7 @@
     "Modified: / 07-01-2012 / 12:59:01 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'startup and exit'!
 
 addExitBlock:aBlock
@@ -4368,6 +4405,7 @@
     "
 ! !
 
+
 !Smalltalk class methodsFor:'startup queries'!
 
 commandLine
@@ -4590,6 +4628,7 @@
     "
 ! !
 
+
 !Smalltalk class methodsFor:'system environment'!
 
 language
@@ -4682,6 +4721,7 @@
     LanguageTerritory := aTerritorySymbol asSymbol.
 ! !
 
+
 !Smalltalk class methodsFor:'system management'!
 
 compressSources
@@ -5316,6 +5356,7 @@
     "Modified: / 20.6.1998 / 12:41:34 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'system management-fileIn'!
 
 fileIn:aFileName
@@ -5629,309 +5670,309 @@
 
     wasLazy := Compiler compileLazy:loadLazy.
     beSilent notNil ifTrue:[
-	wasSilent := self silentLoading:beSilent.
+        wasSilent := self silentLoading:beSilent.
     ].
 
     classFileName := Smalltalk fileNameForClass:aClassName.
     (classFileName = aClassName) ifTrue:[
-	"/ no abbrev.stc translation for className
-	(aClassName includes:$:) ifTrue:[
-	    "/ a nameSpace name
-	    alternativeClassFileName := classFileName copyFrom:(classFileName lastIndexOf:$:)+1
-	].
+        "/ no abbrev.stc translation for className
+        (aClassName includes:$:) ifTrue:[
+            "/ a nameSpace name
+            alternativeClassFileName := classFileName copyFrom:(classFileName lastIndexOf:$:)+1
+        ].
     ].
 
     classFileName asFilename isAbsolute ifTrue:[
-	classFileName asFilename suffix notEmptyOrNil ifTrue:[
-	    ok := self fileIn:classFileName lazy:loadLazy silent:beSilent.
-	] ifFalse:[
-	    ok := self fileInSourceFile:classFileName lazy:loadLazy silent:beSilent.
-	]
+        classFileName asFilename suffix notEmptyOrNil ifTrue:[
+            ok := self fileIn:classFileName lazy:loadLazy silent:beSilent.
+        ] ifFalse:[
+            ok := self fileInSourceFile:classFileName lazy:loadLazy silent:beSilent.
+        ]
     ] ifFalse:[
-	classFileName := classFileName copyReplaceAll:$: with:$_.
-	[
-	    Class withoutUpdatingChangesDo:[
-		|zarFn zar entry|
-
-		ok := false.
-
-		package notNil ifTrue:[
-		    packageDir := package asPackageId projectDirectory.
-		    "/ packageDir := package asString.
-		    "/ packageDir := packageDir copyReplaceAll:$: with:$/.
-		    packageDir isNil ifTrue:[
-			packageDir := self packageDirectoryForPackageId:package
-		    ].
-		].
-
-		Class packageQuerySignal answer:package do:[
-		    "
-		     then, if dynamic linking is available,
-		    "
-		    (LoadBinaries and:[ObjectFileLoader notNil]) ifTrue:[
-			sharedLibExtension := ObjectFileLoader sharedLibraryExtension.
-			"
-			 first look for a class packages shared binary in binary/xxx.o
-			"
-			libName := self libraryFileNameOfClass:aClassName.
-			libName notNil ifTrue:[
-			    (ok := self fileInClass:aClassName fromObject:(libName, sharedLibExtension))
-			    ifFalse:[
-				sharedLibExtension ~= '.o' ifTrue:[
-				    ok := self fileInClass:aClassName fromObject:(libName, '.o')
-				]
-			    ].
-			].
-			"
-			 then, look for a shared binary in binary/xxx.o
-			"
-			ok ifFalse:[
-			    (ok := self fileInClass:aClassName fromObject:(classFileName, sharedLibExtension))
-			    ifFalse:[
-				sharedLibExtension ~= '.o' ifTrue:[
-				    ok := self fileInClass:aClassName fromObject:(classFileName, '.o')
-				].
-				ok ifFalse:[
-				    alternativeClassFileName notNil ifTrue:[
-					(ok := self fileInClass:aClassName fromObject:(alternativeClassFileName, sharedLibExtension))
-					ifFalse:[
-					    sharedLibExtension ~= '.o' ifTrue:[
-						ok := self fileInClass:aClassName fromObject:(alternativeClassFileName, '.o')
-					    ]
-					]
-				    ].
-				].
-			    ].
-			].
-		    ].
-
-		    "
-		     if that did not work, look for a compiled-bytecode file ...
-		    "
-		    ok ifFalse:[
-			(ok := self fileIn:(classFileName , '.cls') lazy:loadLazy silent:beSilent)
-			ifFalse:[
-			    alternativeClassFileName notNil ifTrue:[
-				ok := self fileIn:(alternativeClassFileName , '.cls') lazy:loadLazy silent:beSilent
-			    ]
-			]
-		    ].
-		    "
-		     if that did not work, and the classes package is known,
-		     look for an st-cls file
-		     in a package subdir of the source-directory ...
-		    "
-		    ok ifFalse:[
-			(packageDir notNil and:[BinaryObjectStorage notNil]) ifTrue:[
-			    packageFile := self getPackageFileName:(packageDir , '/classes/' , classFileName , '.cls').
-			    packageFile isNil ifTrue:[
-				packageFile := (packageDir , '/classes/' , classFileName , '.cls').
-			    ].
-			    (ok := self fileIn:packageFile lazy:loadLazy silent:beSilent)
-			    ifFalse:[
-				alternativeClassFileName notNil ifTrue:[
-				    packageFile := self getPackageFileName:(packageDir , '/classes/' , alternativeClassFileName , '.cls').
-				    packageFile isNil ifTrue:[
-					packageFile := (packageDir , '/classes/' , alternativeClassFileName , '.cls').
-				    ].
-				    ok := self fileIn:packageFile lazy:loadLazy silent:beSilent
-				]
-			    ].
-
-			    zarFn := self getPackageFileName:(packageDir , '/classes.zip').
-			    zarFn notNil ifTrue:[
-				zar := ZipArchive oldFileNamed:zarFn.
-				zar notNil ifTrue:[
-				    entry := zar extract:(classFileName , '.cls').
-				    (entry isNil and:[alternativeClassFileName notNil]) ifTrue:[
-					entry := zar extract:(alternativeClassFileName , '.cls').
-				    ].
-				    entry notNil ifTrue:[
-					bos := BinaryObjectStorage onOld:(entry asByteArray readStream).
-					bos next.
-					bos close.
-					ok := true
-				    ].
-				]
-			    ]
-			]
-		    ].
-
-		    "
-		     if that did not work, look for an st-source file ...
-		    "
-		    ok ifFalse:[
-			filenameToSet := classFileName.
-			(ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent)
-			ifFalse:[
-			    alternativeClassFileName notNil ifTrue:[
-				filenameToSet := alternativeClassFileName.
-				ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent
-			    ].
-			    ok ifFalse:[
-				"
-				 ... and in the standard source-directory
-				"
-				filenameToSet := 'source/' , classFileName.
-				(ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent)
-				ifFalse:[
-				    alternativeClassFileName notNil ifTrue:[
-					filenameToSet := 'source/' , alternativeClassFileName.
-					ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent
-				    ]
-				]
-			    ]
-			].
-			"
-			 if that did not work, and the classes package is known,
-			 look for an st-source file
-			 in a package subdir of the source-directory ...
-			"
-			ok ifFalse:[
-			    packageDir notNil ifTrue:[
-				packageFile := self getPackageSourceFileName:(packageDir , '/source/' , classFileName).
-				packageFile isNil ifTrue:[
-				    packageFile := (packageDir , '/source/' , classFileName).
-				].
-				filenameToSet := packageFile.
-				(ok := self fileInSourceFile:packageFile lazy:loadLazy silent:beSilent)
-				ifFalse:[
-				    alternativeClassFileName notNil ifTrue:[
-					packageFile := self getPackageSourceFileName:(packageDir , '/source/' , alternativeClassFileName).
-					packageFile isNil ifTrue:[
-					    packageFile := (packageDir , '/source/' , alternativeClassFileName).
-					].
-					filenameToSet := packageFile.
-					ok := self fileInSourceFile:packageFile lazy:loadLazy silent:beSilent
-				    ].
-				    ok ifFalse:[
-					packageFile := self getPackageSourceFileName:(packageDir , '/' , classFileName).
-					packageFile isNil ifTrue:[
-					    packageFile := (packageDir , '/' , classFileName).
-					].
-					filenameToSet := packageFile.
-					(ok := self fileInSourceFile:packageFile lazy:loadLazy silent:beSilent)
-					ifFalse:[
-					    alternativeClassFileName notNil ifTrue:[
-						packageFile := self getPackageFileName:(packageDir , '/' , alternativeClassFileName).
-						packageFile isNil ifTrue:[
-						    packageFile := (packageDir , '/' , alternativeClassFileName).
-						].
-						filenameToSet := packageFile.
-						ok := self fileInSourceFile:packageFile lazy:loadLazy silent:beSilent
-					    ].
-					    ok ifFalse:[
-						"
-						 ... and in the standard source-directory
-						"
-						filenameToSet := 'source/' , packageDir , '/' , classFileName.
-						(ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent)
-						ifFalse:[
-						    alternativeClassFileName notNil ifTrue:[
-							filenameToSet := 'source/' , packageDir , '/' , alternativeClassFileName.
-							ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent
-						    ]
-						]
-					    ]
-					].
-				    ].
-				].
-			    ]
-			].
-			"
-			 if that did not work, and the classes package is known,
-			 look for a zipArchive containing a class entry.
-			"
-			ok ifFalse:[
-			    packageDir notNil ifTrue:[
-				zarFn := self getPackageFileName:(packageDir , '/source.zip').
-				zarFn isNil ifTrue:[
-				    zarFn := packageDir asFilename withSuffix:'zip'.
-				    zarFn := self getSourceFileName:zarFn.
-				].
-				(zarFn notNil and:[zarFn asFilename exists]) ifTrue:[
-				    zar := ZipArchive oldFileNamed:zarFn.
-				    zar notNil ifTrue:[
-					entry := zar extract:(classFileName , '.st').
-					(entry isNil and:[alternativeClassFileName notNil]) ifTrue:[
-					    entry := zar extract:(alternativeClassFileName , '.st').
-					].
-					entry notNil ifTrue:[
-					    filenameToSet := zarFn.
-					    ok := self
-						    fileInStream:(entry asString readStream)
-						    lazy:loadLazy
-						    silent:beSilent
-						    logged:false
-						    addPath:nil
-					].
-				    ]
-				]
-			    ]
-			].
-
-			"
-			 if that did not work,
-			 look for a zipArchive containing a class entry.
-			"
-			ok ifFalse:[
-			    zarFn := self getSourceFileName:'source.zip'.
-			    zarFn notNil ifTrue:[
-				zar := ZipArchive oldFileNamed:zarFn.
-				zar notNil ifTrue:[
-				    entry := zar extract:(zarFn := classFileName , '.st').
-				    (entry isNil and:[alternativeClassFileName notNil]) ifTrue:[
-					entry := zar extract:(zarFn := alternativeClassFileName , '.st').
-				    ].
-				    entry notNil ifTrue:[
-					filenameToSet := zarFn.
-					ok := self
-						fileInStream:(entry asString readStream)
-						lazy:loadLazy
-						silent:beSilent
-						logged:false
-						addPath:nil
-				    ].
-				]
-			    ]
-			].
-			ok ifFalse:[
-			    "
-			     if there is a sourceCodeManager, ask it for the classes sourceCode
-			    "
-			    (mgr := Smalltalk at:#SourceCodeManager) notNil ifTrue:[
-				inStream := mgr getMostRecentSourceStreamForClassNamed:aClassName inPackage:package.
-				inStream notNil ifTrue:[
-				    filenameToSet := nil.
-				    ok := self fileInStream:inStream lazy:loadLazy silent:beSilent logged:false addPath:nil.
-				]
-			    ].
-			].
-		    ].
-		]
-	    ].
-	] ensure:[
-	    Compiler compileLazy:wasLazy.
-	    wasSilent notNil ifTrue:[
-		self silentLoading:wasSilent
-	    ]
-	].
+        classFileName := classFileName copyReplaceAll:$: with:$_.
+        [
+            Class withoutUpdatingChangesDo:[
+                |zarFn zar entry|
+
+                ok := false.
+
+                package notNil ifTrue:[
+                    packageDir := package asPackageId projectDirectory.
+                    "/ packageDir := package asString.
+                    "/ packageDir := packageDir copyReplaceAll:$: with:$/.
+                    packageDir isNil ifTrue:[
+                        packageDir := self packageDirectoryForPackageId:package
+                    ].
+                ].
+
+                Class packageQuerySignal answer:package do:[
+                    "
+                     then, if dynamic linking is available,
+                    "
+                    (LoadBinaries and:[ObjectFileLoader notNil]) ifTrue:[
+                        sharedLibExtension := ObjectFileLoader sharedLibraryExtension.
+                        "
+                         first look for a class packages shared binary in binary/xxx.o
+                        "
+                        libName := self libraryFileNameOfClass:aClassName.
+                        libName notNil ifTrue:[
+                            (ok := self fileInClass:aClassName fromObject:(libName, sharedLibExtension))
+                            ifFalse:[
+                                sharedLibExtension ~= '.o' ifTrue:[
+                                    ok := self fileInClass:aClassName fromObject:(libName, '.o')
+                                ]
+                            ].
+                        ].
+                        "
+                         then, look for a shared binary in binary/xxx.o
+                        "
+                        ok ifFalse:[
+                            (ok := self fileInClass:aClassName fromObject:(classFileName, sharedLibExtension))
+                            ifFalse:[
+                                sharedLibExtension ~= '.o' ifTrue:[
+                                    ok := self fileInClass:aClassName fromObject:(classFileName, '.o')
+                                ].
+                                ok ifFalse:[
+                                    alternativeClassFileName notNil ifTrue:[
+                                        (ok := self fileInClass:aClassName fromObject:(alternativeClassFileName, sharedLibExtension))
+                                        ifFalse:[
+                                            sharedLibExtension ~= '.o' ifTrue:[
+                                                ok := self fileInClass:aClassName fromObject:(alternativeClassFileName, '.o')
+                                            ]
+                                        ]
+                                    ].
+                                ].
+                            ].
+                        ].
+                    ].
+
+                    "
+                     if that did not work, look for a compiled-bytecode file ...
+                    "
+                    ok ifFalse:[
+                        (ok := self fileIn:(classFileName , '.cls') lazy:loadLazy silent:beSilent)
+                        ifFalse:[
+                            alternativeClassFileName notNil ifTrue:[
+                                ok := self fileIn:(alternativeClassFileName , '.cls') lazy:loadLazy silent:beSilent
+                            ]
+                        ]
+                    ].
+                    "
+                     if that did not work, and the classes package is known,
+                     look for an st-cls file
+                     in a package subdir of the source-directory ...
+                    "
+                    ok ifFalse:[
+                        (packageDir notNil and:[BinaryObjectStorage notNil]) ifTrue:[
+                            packageFile := self getPackageFileName:(packageDir , '/classes/' , classFileName , '.cls').
+                            packageFile isNil ifTrue:[
+                                packageFile := (packageDir , '/classes/' , classFileName , '.cls').
+                            ].
+                            (ok := self fileIn:packageFile lazy:loadLazy silent:beSilent)
+                            ifFalse:[
+                                alternativeClassFileName notNil ifTrue:[
+                                    packageFile := self getPackageFileName:(packageDir , '/classes/' , alternativeClassFileName , '.cls').
+                                    packageFile isNil ifTrue:[
+                                        packageFile := (packageDir , '/classes/' , alternativeClassFileName , '.cls').
+                                    ].
+                                    ok := self fileIn:packageFile lazy:loadLazy silent:beSilent
+                                ]
+                            ].
+
+                            zarFn := self getPackageFileName:(packageDir , '/classes.zip').
+                            zarFn notNil ifTrue:[
+                                zar := ZipArchive oldFileNamed:zarFn.
+                                zar notNil ifTrue:[
+                                    entry := zar extract:(classFileName , '.cls').
+                                    (entry isNil and:[alternativeClassFileName notNil]) ifTrue:[
+                                        entry := zar extract:(alternativeClassFileName , '.cls').
+                                    ].
+                                    entry notNil ifTrue:[
+                                        bos := BinaryObjectStorage onOld:(entry asByteArray readStream).
+                                        bos next.
+                                        bos close.
+                                        ok := true
+                                    ].
+                                ]
+                            ]
+                        ]
+                    ].
+
+                    "
+                     if that did not work, look for an st-source file ...
+                    "
+                    ok ifFalse:[
+                        filenameToSet := classFileName.
+                        (ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent)
+                        ifFalse:[
+                            alternativeClassFileName notNil ifTrue:[
+                                filenameToSet := alternativeClassFileName.
+                                ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent
+                            ].
+                            ok ifFalse:[
+                                "
+                                 ... and in the standard source-directory
+                                "
+                                filenameToSet := 'source/' , classFileName.
+                                (ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent)
+                                ifFalse:[
+                                    alternativeClassFileName notNil ifTrue:[
+                                        filenameToSet := 'source/' , alternativeClassFileName.
+                                        ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent
+                                    ]
+                                ]
+                            ]
+                        ].
+                        "
+                         if that did not work, and the classes package is known,
+                         look for an st-source file
+                         in a package subdir of the source-directory ...
+                        "
+                        ok ifFalse:[
+                            packageDir notNil ifTrue:[
+                                packageFile := self getPackageSourceFileName:(packageDir , '/source/' , classFileName).
+                                packageFile isNil ifTrue:[
+                                    packageFile := (packageDir , '/source/' , classFileName).
+                                ].
+                                filenameToSet := packageFile.
+                                (ok := self fileInSourceFile:packageFile lazy:loadLazy silent:beSilent)
+                                ifFalse:[
+                                    alternativeClassFileName notNil ifTrue:[
+                                        packageFile := self getPackageSourceFileName:(packageDir , '/source/' , alternativeClassFileName).
+                                        packageFile isNil ifTrue:[
+                                            packageFile := (packageDir , '/source/' , alternativeClassFileName).
+                                        ].
+                                        filenameToSet := packageFile.
+                                        ok := self fileInSourceFile:packageFile lazy:loadLazy silent:beSilent
+                                    ].
+                                    ok ifFalse:[
+                                        packageFile := self getPackageSourceFileName:(packageDir , '/' , classFileName).
+                                        packageFile isNil ifTrue:[
+                                            packageFile := (packageDir , '/' , classFileName).
+                                        ].
+                                        filenameToSet := packageFile.
+                                        (ok := self fileInSourceFile:packageFile lazy:loadLazy silent:beSilent)
+                                        ifFalse:[
+                                            alternativeClassFileName notNil ifTrue:[
+                                                packageFile := self getPackageFileName:(packageDir , '/' , alternativeClassFileName).
+                                                packageFile isNil ifTrue:[
+                                                    packageFile := (packageDir , '/' , alternativeClassFileName).
+                                                ].
+                                                filenameToSet := packageFile.
+                                                ok := self fileInSourceFile:packageFile lazy:loadLazy silent:beSilent
+                                            ].
+                                            ok ifFalse:[
+                                                "
+                                                 ... and in the standard source-directory
+                                                "
+                                                filenameToSet := 'source/' , packageDir , '/' , classFileName.
+                                                (ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent)
+                                                ifFalse:[
+                                                    alternativeClassFileName notNil ifTrue:[
+                                                        filenameToSet := 'source/' , packageDir , '/' , alternativeClassFileName.
+                                                        ok := self fileInSourceFile:filenameToSet lazy:loadLazy silent:beSilent
+                                                    ]
+                                                ]
+                                            ]
+                                        ].
+                                    ].
+                                ].
+                            ]
+                        ].
+                        "
+                         if that did not work, and the classes package is known,
+                         look for a zipArchive containing a class entry.
+                        "
+                        ok ifFalse:[
+                            packageDir notNil ifTrue:[
+                                zarFn := self getPackageFileName:(packageDir , '/source.zip').
+                                zarFn isNil ifTrue:[
+                                    zarFn := packageDir asFilename withSuffix:'zip'.
+                                    zarFn := self getSourceFileName:zarFn.
+                                ].
+                                (zarFn notNil and:[zarFn asFilename exists]) ifTrue:[
+                                    zar := ZipArchive oldFileNamed:zarFn.
+                                    zar notNil ifTrue:[
+                                        entry := zar extract:(classFileName , '.st').
+                                        (entry isNil and:[alternativeClassFileName notNil]) ifTrue:[
+                                            entry := zar extract:(alternativeClassFileName , '.st').
+                                        ].
+                                        entry notNil ifTrue:[
+                                            filenameToSet := zarFn.
+                                            ok := self
+                                                    fileInStream:(entry asString readStream)
+                                                    lazy:loadLazy
+                                                    silent:beSilent
+                                                    logged:false
+                                                    addPath:nil
+                                        ].
+                                    ]
+                                ]
+                            ]
+                        ].
+
+                        "
+                         if that did not work,
+                         look for a zipArchive containing a class entry.
+                        "
+                        ok ifFalse:[
+                            zarFn := self getSourceFileName:'source.zip'.
+                            zarFn notNil ifTrue:[
+                                zar := ZipArchive oldFileNamed:zarFn.
+                                zar notNil ifTrue:[
+                                    entry := zar extract:(zarFn := classFileName , '.st').
+                                    (entry isNil and:[alternativeClassFileName notNil]) ifTrue:[
+                                        entry := zar extract:(zarFn := alternativeClassFileName , '.st').
+                                    ].
+                                    entry notNil ifTrue:[
+                                        filenameToSet := zarFn.
+                                        ok := self
+                                                fileInStream:(entry asString readStream)
+                                                lazy:loadLazy
+                                                silent:beSilent
+                                                logged:false
+                                                addPath:nil
+                                    ].
+                                ]
+                            ]
+                        ].
+                        ok ifFalse:[
+                            "
+                             if there is a sourceCodeManager, ask it for the classes sourceCode
+                            "
+                            (mgr := Smalltalk at:#SourceCodeManager) notNil ifTrue:[
+                                inStream := mgr getMostRecentSourceStreamForClassNamed:aClassName inPackage:package.
+                                inStream notNil ifTrue:[
+                                    filenameToSet := nil.
+                                    ok := self fileInStream:inStream lazy:loadLazy silent:beSilent logged:false addPath:nil.
+                                ]
+                            ].
+                        ].
+                    ].
+                ]
+            ].
+        ] ensure:[
+            Compiler compileLazy:wasLazy.
+            wasSilent notNil ifTrue:[
+                self silentLoading:wasSilent
+            ]
+        ].
     ].
 
     ok ifTrue:[
-	newClass := self at:(aClassName asSymbol).
-	newClass notNil ifTrue:[
-	    "set the classes name - but do not change if already set"
-	    filenameToSet notNil ifTrue:[
-		newClass getClassFilename isNil ifTrue:[
-		    newClass setClassFilename:(filenameToSet asFilename baseName)
-		].
-	    ].
-
-	    doInit ifTrue:[
-		newClass initialize
-	    ]
-	]
+        newClass := self at:(aClassName asSymbol).
+        newClass notNil ifTrue:[
+            "set the classes name - but do not change if already set"
+            filenameToSet notNil ifTrue:[
+                newClass getClassFilename isNil ifTrue:[
+                    newClass setClassFilename:(filenameToSet asFilename baseName)
+                ].
+            ].
+
+            doInit ifTrue:[
+                newClass initialize
+            ]
+        ]
     ].
 
     ^ newClass
@@ -6178,6 +6219,7 @@
     ].
 ! !
 
+
 !Smalltalk class methodsFor:'system management-files'!
 
 bitmapFileStreamFor:aFileName
@@ -6280,54 +6322,77 @@
     "return a actual or expected (or most wanted) filename for aClassOrClassName
      - only the base name (without directory part) and without suffix."
 
-    |cls nonMetaclass nm nameWithPrefix nameWithoutPrefix|
+    |cls nonMetaclass nm nameWithPrefix nameWithoutPrefix compatQuery compatPkg |
 
 "/  This was added as an extension of libsvn - should be no longer needed
-"/    compatQuery := Smalltalk classNamed: 'SVN::CompatModeQuery'.
-"/    (compatQuery notNil
-"/      and:[compatQuery isLoaded
-"/        and:[compatQuery query not]]) ifTrue:[
-"/            nm := aClassOrClassName isBehavior
-"/                ifTrue:[aClassOrClassName name]
-"/                ifFalse:[aClassOrClassName].
-"/            nm := nm copyReplaceAll:$: with:$_.
-"/            ^nm
-"/    ].
+"/  JV@2012-09-25: but it actually is. The problem is that class filename
+"/  is stored in the class itself and used to generate abbrev.stc and
+"/  prerequisites in makefiles. But if you renamed such a stc-compiled class,
+"/  the filename remains the same, but SVN __ALWAYS__ keep container name
+"/  and class name in sync. Therefore build files gets messed up. Indeed, this
+"/  should be fixed in code that files-out the package and generates build files.
+"/  Certainly a hack, but do not remove this until fixed elsewhere
+
+    compatQuery := Smalltalk classNamed: 'SVN::CompatModeQuery'.
+    (compatQuery notNil
+      and:[compatQuery isLoaded
+        and:[compatQuery query not]]) ifTrue:[
+            nm := aClassOrClassName isBehavior
+                ifTrue:[aClassOrClassName name]
+                ifFalse:[aClassOrClassName].
+            nm := nm copyReplaceAll:$: with:$_.
+            ^nm
+    ].
+
+"/  Same for another query for new libscm...
+    compatQuery := Smalltalk classNamed: 'SCMCompatModeQuery'.
+    (compatQuery notNil
+      and:[compatQuery isLoaded
+        and:[(compatPkg := compatQuery query) notNil]]) ifTrue:[
+            nm := aClassOrClassName isBehavior
+                ifTrue:[aClassOrClassName name]
+                ifFalse:[aClassOrClassName].
+            cls := Smalltalk at: nm asSymbol.
+            (cls notNil and:[cls package == compatPkg]) ifTrue:[
+                nm := nm copyReplaceAll:$: with:$_.
+                ^nm
+            ].
+    ].
 
     aClassOrClassName isBehavior ifTrue:[
-	cls := aClassOrClassName.
+        cls := aClassOrClassName.
     ] ifFalse:[
-	cls := Smalltalk classNamed:aClassOrClassName.
-	cls isNil ifTrue:[
-	    nameWithPrefix := aClassOrClassName.
-	    nameWithoutPrefix := (aClassOrClassName copyFrom:(aClassOrClassName lastIndexOf:$:)+1).
-	].
+        cls := Smalltalk classNamed:aClassOrClassName.
+        cls isNil ifTrue:[
+            nameWithPrefix := aClassOrClassName.
+            nameWithoutPrefix := (aClassOrClassName copyFrom:(aClassOrClassName lastIndexOf:$:)+1).
+        ].
     ].
 
     cls notNil ifTrue:[
-	nonMetaclass := cls theNonMetaclass.
-	nm := nonMetaclass getClassFilename.
-	nm isNil ifTrue:[
-	    cls revisionInfo notNil ifTrue:[
-		nm := cls revisionInfo fileName.
-	    ].
-	].
-	nm notNil ifTrue:[
-	    ^ nm asFilename withoutSuffix baseName
-	].
-	nameWithPrefix := nonMetaclass name.
-	nameWithoutPrefix := nonMetaclass nameWithoutPrefix.
+        nonMetaclass := cls theNonMetaclass.
+        nm := nonMetaclass getClassFilename.
+        nm isNil ifTrue:[
+            cls revisionInfo notNil ifTrue:[
+                nm := cls revisionInfo fileName.
+            ].
+        ].
+        nm notNil ifTrue:[
+            ^ nm asFilename withoutSuffix baseName
+        ].
+        nameWithPrefix := nonMetaclass name.
+        nameWithoutPrefix := nonMetaclass nameWithoutPrefix.
     ].
 
     CachedAbbreviations notNil ifTrue:[
-	nameWithPrefix := nameWithPrefix asSymbol.
-	(CachedAbbreviations includesKey:nameWithPrefix) ifTrue:[
-	    ^ (CachedAbbreviations at:nameWithPrefix) asFilename baseName
-	].
-	nameWithoutPrefix := nameWithoutPrefix asSymbol.
-	(CachedAbbreviations includesKey:nameWithoutPrefix) ifTrue:[
-	    ^ (CachedAbbreviations at:nameWithoutPrefix) asFilename baseName
-	].
+        nameWithPrefix := nameWithPrefix asSymbol.
+        (CachedAbbreviations includesKey:nameWithPrefix) ifTrue:[
+            ^ (CachedAbbreviations at:nameWithPrefix) asFilename baseName
+        ].
+        nameWithoutPrefix := nameWithoutPrefix asSymbol.
+        (CachedAbbreviations includesKey:nameWithoutPrefix) ifTrue:[
+            ^ (CachedAbbreviations at:nameWithoutPrefix) asFilename baseName
+        ].
     ].
 
     ^ nameWithPrefix copyReplaceAll:$: with:$_
@@ -6347,6 +6412,8 @@
     "
 
     "Modified: / 06-10-2006 / 16:16:01 / cg"
+    "Modified: / 04-12-2012 / 17:44:26 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    "Modified (format): / 05-12-2012 / 10:47:46 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 filenameAbbreviations
@@ -7428,6 +7495,7 @@
     "Modified: / 04-08-2011 / 21:35:00 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'system management-packages'!
 
 loadPackage:aPackageIdOrPackage
@@ -7458,7 +7526,7 @@
 
     packageDir := self getPackageFileName:packageDirName.
     packageDir isNil ifTrue:[
-	^ nil.
+        ^ nil.
     ].
     ^ packageDir asFilename
 
@@ -7474,11 +7542,11 @@
 
     projectDefinition := aPackageIdOrPackage.
     projectDefinition isProjectDefinition ifFalse:[
-	projectDefinition := projectDefinition asPackageId projectDefinitionClass.
-	projectDefinition isNil ifTrue:[
-	    'Smalltalk [info] trying to unload non-existing package: ' infoPrint. aPackageIdOrPackage infoPrintCR.
-	    ^ self.
-	].
+        projectDefinition := projectDefinition asPackageId projectDefinitionClass.
+        projectDefinition isNil ifTrue:[
+            'Smalltalk [info] trying to unload non-existing package: ' infoPrint. aPackageIdOrPackage infoPrintCR.
+            ^ self.
+        ].
     ].
     projectDefinition unloadPackage.
 
@@ -7488,6 +7556,7 @@
     "
 ! !
 
+
 !Smalltalk class methodsFor:'system management-undeclared variables'!
 
 clearUndeclaredVariables
@@ -7508,6 +7577,7 @@
     "Created: / 31.10.1997 / 01:13:10 / cg"
 ! !
 
+
 !Smalltalk class methodsFor:'time-versions'!
 
 configuration
@@ -7764,13 +7834,13 @@
      Now releaseNr is the build number (BUILD_NUMBER from Jenkins)
 
      ST/X revision Naming is:
-	<major>.<minor>.<revision>.<release>"
+        <major>.<minor>.<revision>.<release>"
 
     |releaseNumber|
 
     releaseNumber := Smalltalk versionBuildNumber.
     releaseNumber isEmpty ifTrue:[
-	^ 0.
+        ^ 0.
     ].
     ^ releaseNumber
 
@@ -7792,7 +7862,7 @@
      to the outside world.
 
      ST/X revision Naming is:
-	<major>.<minor>.<revision>.<release>"
+        <major>.<minor>.<revision>.<release>"
 
     ^ 3
 
@@ -7881,7 +7951,7 @@
        self minorVersionNr printString ,
        '.',
        self revisionNr printString,
-       '.',
+       'jv.',
        self releaseNr printString)
 
 
@@ -7904,6 +7974,7 @@
     "
 ! !
 
+
 !Smalltalk class methodsFor:'documentation'!
 
 version
@@ -7914,6 +7985,11 @@
     ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.1018 2013-03-27 19:13:42 cg Exp $'
 !
 
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
+!
+
 version_SVN
     ^ '§ Id: Smalltalk.st 10648 2011-06-23 15:55:10Z vranyj1  §'
 ! !
--- a/SmalltalkChunkFileSourceWriter.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/SmalltalkChunkFileSourceWriter.st	Thu Mar 28 12:21:50 2013 +0000
@@ -532,7 +532,17 @@
         [:method| |cat source privacy|
 
         stream nextPutChunkSeparator.
-        method mclass name printOn:stream.
+        "JV@2012-09-05: Support for filing out Java extension methods"
+        method mclass theNonMetaclass isJavaClass ifTrue:[
+            stream nextPutAll:'(Java classForName:'''.
+            stream nextPutAll:(method mclass theNonMetaclass name copyReplaceAll:$/ with: $.).
+            stream nextPutAll:''')'.
+            method mclass isMetaclass ifTrue:[
+                stream nextPutAll: ' class'.
+            ].
+        ] ifFalse:[
+            method mclass name printOn:stream.
+        ].
         "/        self printClassNameOn:aStream.
 
         (privacy := method privacy) ~~ #public ifTrue:[
--- a/SnapshotError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/SnapshotError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 Error subclass:#SnapshotError
@@ -44,7 +43,14 @@
 !SnapshotError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SnapshotError.st,v 1.3 2005-03-29 22:25:15 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/SnapshotError.st,v 1.3 2005/03/29 22:25:15 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: SnapshotError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 SnapshotError initialize!
+
+
+
--- a/SomeNumber.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/SomeNumber.st	Thu Mar 28 12:21:50 2013 +0000
@@ -110,5 +110,13 @@
 !SomeNumber class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SomeNumber.st,v 1.3 2003-07-02 09:52:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/SomeNumber.st,v 1.3 2003/07/02 09:52:23 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: SomeNumber.st 10790 2012-03-13 15:46:50Z vranyj1 $'
+
 ! !
+
+
+
--- a/StreamIOError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/StreamIOError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#StreamIOError
@@ -38,5 +37,12 @@
 !StreamIOError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/StreamIOError.st,v 1.2 2005-02-02 11:03:44 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/StreamIOError.st,v 1.2 2005/02/02 11:03:44 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: StreamIOError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/StreamNotOpenError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/StreamNotOpenError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#StreamNotOpenError
@@ -44,5 +43,12 @@
 !StreamNotOpenError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/StreamNotOpenError.st,v 1.3 2005-02-02 10:59:49 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/StreamNotOpenError.st,v 1.3 2005/02/02 10:59:49 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: StreamNotOpenError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/SubscriptOutOfBoundsError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/SubscriptOutOfBoundsError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 IndexNotFoundError subclass:#SubscriptOutOfBoundsError
@@ -45,5 +44,12 @@
 !SubscriptOutOfBoundsError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SubscriptOutOfBoundsError.st,v 1.4 2003-08-29 19:15:03 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/SubscriptOutOfBoundsError.st,v 1.4 2003/08/29 19:15:03 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: SubscriptOutOfBoundsError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/SystemNotification.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/SystemNotification.st	Thu Mar 28 12:21:50 2013 +0000
@@ -37,5 +37,8 @@
 !SystemNotification class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SystemNotification.st,v 1.3 2008-10-04 08:42:18 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/SystemNotification.st,v 1.3 2008/10/04 08:42:18 cg Exp $'
 ! !
+
+
+
--- a/TerminateProcessRequest.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/TerminateProcessRequest.st	Thu Mar 28 12:21:50 2013 +0000
@@ -68,5 +68,12 @@
 !TerminateProcessRequest class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/TerminateProcessRequest.st,v 1.3 2007-11-07 10:37:10 ca Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/TerminateProcessRequest.st,v 1.3 2007/11/07 10:37:10 ca Exp $'
+!
+
+version_SVN
+    ^ '$Id: TerminateProcessRequest.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/TextCollectorStream.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/TextCollectorStream.st	Thu Mar 28 12:21:50 2013 +0000
@@ -195,5 +195,8 @@
 !TextCollectorStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/TextCollectorStream.st,v 1.2 2006-04-06 10:54:06 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/TextCollectorStream.st,v 1.2 2006/04/06 10:54:06 stefan Exp $'
 ! !
+
+
+
--- a/TimeConversionError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/TimeConversionError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -43,7 +43,14 @@
 !TimeConversionError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/TimeConversionError.st,v 1.1 2008-08-06 09:22:57 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/TimeConversionError.st,v 1.1 2008/08/06 09:22:57 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: TimeConversionError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 TimeConversionError initialize!
+
+
+
--- a/TimeoutError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/TimeoutError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#TimeoutError
@@ -67,7 +66,14 @@
 !TimeoutError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/TimeoutError.st,v 1.5 2004-08-22 17:47:07 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/TimeoutError.st,v 1.5 2004/08/22 17:47:07 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: TimeoutError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 TimeoutError initialize!
+
+
+
--- a/UnboundedExternalStream.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UnboundedExternalStream.st	Thu Mar 28 12:21:50 2013 +0000
@@ -67,5 +67,8 @@
 !UnboundedExternalStream class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UnboundedExternalStream.st,v 1.8 1996-04-25 17:02:20 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UnboundedExternalStream.st,v 1.8 1996/04/25 17:02:20 cg Exp $'
 ! !
+
+
+
--- a/UnderflowError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UnderflowError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -41,16 +41,22 @@
 "
 ! !
 
+
 !UnderflowError class methodsFor:'initialization'!
 
 initialize
     NotifierString := 'underflow'.
 ! !
 
+
 !UnderflowError class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/UnderflowError.st,v 1.4 2013-03-13 23:43:59 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: UnderflowError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 
--- a/UnimplementedFunctionalityError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UnimplementedFunctionalityError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ProceedableError subclass:#UnimplementedFunctionalityError
@@ -63,7 +62,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: /cvs/stx/stx/libbasic/UnimplementedFunctionalityError.st,v 1.2 2006/03/03 19:13:11 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: UnimplementedFunctionalityError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 UnimplementedFunctionalityError initialize!
+
+
+
--- a/UnixFileHandle.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UnixFileHandle.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 OSFileHandle subclass:#UnixFileHandle
@@ -60,5 +59,12 @@
 !UnixFileHandle class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UnixFileHandle.st,v 1.4 2003-08-30 12:36:42 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UnixFileHandle.st,v 1.4 2003/08/30 12:36:42 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: UnixFileHandle.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/UnixOperatingSystem.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UnixOperatingSystem.st	Thu Mar 28 12:21:50 2013 +0000
@@ -16,7 +16,7 @@
 	classVariableNames:'HostName DomainName SlowFork ForkFailed CurrentDirectory
 		LastTimeInfo LastTimeInfoSeconds LastTimeInfoMilliseconds
 		LastTimeInfoIsLocal CachedMountPoints CacheMountPointsTimeStamp
-		Codeset'
+		Codeset CodesetEncoder'
 	poolDictionaries:''
 	category:'OS-Unix'
 !
@@ -528,341 +528,6 @@
 %}
 ! !
 
-!UnixOperatingSystem primitiveFunctions!
-%{
-
-/*
- * some systems' system() is broken in that it does not correctly
- * handle EINTR and returns failure even though it actually succeeded.
- * (LINUX is one of them)
- * Here is a fixed version. If you encounter EINTR returns from
- * UnixOperatingSystem>>executeCommand, you ought to define WANT_SYSTEM
- * in the xxxIntern.h file to get this fixed version.
- *
- * As an added BONUS, this system() enables interrupts while waiting
- * for the child which enables other threads to continue.
- * (i.e. it is RT safe)
- */
-
-#if defined(WANT_SYSTEM)
-
-/* # define DPRINTF(x)     printf x */
-# define DPRINTF(x)     /* nothing */
-
-# ifndef _STDDEF_H_INCLUDED_
-#  include <stddef.h>
-#  define _STDDEF_H_INCLUDED_
-# endif
-
-# ifndef _STDLIB_H_INCLUDED_
-#  include <stdlib.h>
-#  define _STDLIB_H_INCLUDED_
-# endif
-
-# ifndef _UNISTD_H_INCLUDED_
-#  include <unistd.h>
-#  define _UNISTD_H_INCLUDED_
-# endif
-
-# ifndef _SYS_WAIT_H_INCLUDED
-#  include <sys/wait.h>
-#  define _SYS_WAIT_H_INCLUDED
-# endif
-
-# ifndef _SIGNAL_H_INCLUDED_
-#  include <signal.h>
-#  define _SIGNAL_H_INCLUDED_
-# endif
-
-# ifndef _SYS_TYPES_H_INCLUDED_
-#  include <sys/types.h>
-#  define _SYS_TYPES_H_INCLUDED_
-# endif
-
-# if (!defined(HAVE_GNU_LD) && !defined (__ELF__)) || !defined(LINUX)
-#  define       __environ       environ
-#  if 1 /* !defined(LINUX) */
-#   define      __sigemptyset   sigemptyset
-#   define      __sigaction     sigaction
-#   define      __sigaddset     sigaddset
-#   define      __sigprocmask   sigprocmask
-#   define      __execve        execve
-#   define      __wait          wait
-#   define      __waitpid       waitpid
-#  endif /* ! LINUX */
-// #  ifndef __osx__
-    extern char **environ;
-// #  endif
-# endif
-
-# define      __sigprocmask   sigprocmask
-# define      __execve        execve
-
-# define        SHELL_PATH      "/bin/sh"       /* Path of the shell.  */
-# define        SHELL_NAME      "sh"            /* Name to give it.  */
-
-
-static int
-mySystem(line)
-    register CONST char *line;
-{
-    int status, save;
-    pid_t pid;
-    struct sigaction sa, intr, quit;
-    sigset_t block, omask;
-
-    if (line == NULL)
-	return -1;
-
-    sa.sa_handler = SIG_IGN;
-    sa.sa_flags = 0;
-    __sigemptyset (&sa.sa_mask);
-
-    if (__sigaction (SIGINT, &sa, &intr) < 0) {
-	DPRINTF(("1: errno=%d\n", errno));
-	return -1;
-    }
-    if (__sigaction (SIGQUIT, &sa, &quit) < 0) {
-	save = errno;
-	(void) __sigaction (SIGINT, &intr, (struct sigaction *) NULL);
-	errno = save;
-	DPRINTF(("2: errno=%d\n", errno));
-	return -1;
-    }
-
-    __sigemptyset (&block);
-    __sigaddset (&block, SIGCHLD);
-    save = errno;
-    if (__sigprocmask(SIG_BLOCK, &block, &omask) < 0) {
-	if (errno == ENOSYS)
-	    errno = save;
-	else {
-	    save = errno;
-	    (void) __sigaction(SIGINT, &intr, (struct sigaction *) NULL);
-	    (void) __sigaction (SIGQUIT, &quit, (struct sigaction *) NULL);
-	    errno = save;
-	    DPRINTF(("3: errno=%d\n", errno));
-	    return -1;
-	}
-    }
-
-    pid = FORK ();
-    if (pid == (pid_t) 0) {
-	/* Child side.  */
-	CONST char *new_argv[4];
-	new_argv[0] = SHELL_NAME;
-	new_argv[1] = "-c";
-	new_argv[2] = line;
-	new_argv[3] = NULL;
-
-	/* Restore the signals.  */
-	(void) __sigaction (SIGINT, &intr, (struct sigaction *) NULL);
-	(void) __sigaction (SIGQUIT, &quit, (struct sigaction *) NULL);
-	(void) __sigprocmask (SIG_SETMASK, &omask, (sigset_t *) NULL);
-
-	/* Exec the shell.  */
-	(void) __execve (SHELL_PATH, (char *CONST *) new_argv, __environ);
-	_exit (127);
-    } else {
-	if (pid < (pid_t) 0) {
-	    /* The fork failed.  */
-	    DPRINTF(("4: errno=%d\n", errno));
-	    status = -1;
-	} else {
-	    /* Parent side.  */
-#ifdef  NO_WAITPID
-	    pid_t child;
-
-	    do {
-		__BEGIN_INTERRUPTABLE__
-		child = __wait (&status);
-		__END_INTERRUPTABLE__
-		if (child < 0 && errno != EINTR) {
-		    DPRINTF(("5: errno=%d\n", errno));
-		    status = -1;
-		    break;
-		}
-	    } while (child != pid);
-#else
-	    pid_t child;
-
-	    /* claus: the original did not care for EINTR here ... */
-	    do {
-		__BEGIN_INTERRUPTABLE__
-		child = __waitpid (pid, &status, 0);
-		__END_INTERRUPTABLE__
-	    } while ((child != pid) && (errno == EINTR));
-	    if (child != pid) {
-		DPRINTF(("6: errno=%d\n", errno));
-		status = -1;
-	    }
-#endif /* NO_WAITPID */
-	}
-    }
-    save = errno;
-    if ((__sigaction (SIGINT, &intr, (struct sigaction *) NULL)
-     | __sigaction (SIGQUIT, &quit, (struct sigaction *) NULL)
-     | __sigprocmask (SIG_SETMASK, &omask, (sigset_t *) NULL)) != 0) {
-	if (errno == ENOSYS) {
-	    errno = save;
-	} else {
-	    status = -1;
-	    DPRINTF(("7: errno=%d\n", errno));
-	}
-    }
-
-    return status;
-}
-#else
-# define __wait wait
-#endif /* WANT_SYSTEM */
-
-
-/*
- * some systems do not have realpath();
- * the alternative of reading from a 'pwp'-pipe
- * is way too slow. Here is a realpath for the rest of us.
- * define WANT_REALPATH in the xxxIntern-file to get it.
- */
-
-#if defined(HAS_REALPATH)
-# undef WANT_REALPATH
-#endif
-#if !defined(HAS_GETWD) && !defined(HAS_GETCWD)
-# undef WANT_REALPATH
-#endif
-
-#if defined(WANT_REALPATH)
-
-# ifndef NULL
-#  define NULL (char *)0
-# endif
-
-# define MAX_READLINKS 32
-
-# ifndef MAXPATHLEN
-#  define MAXPATHLEN     1024
-# endif
-
-static
-char *
-realpath(path, resolved_path)
-    char *path;
-    char resolved_path [];
-{
-	char copy_path[MAXPATHLEN];
-	char link_path[MAXPATHLEN];
-	char *new_path = resolved_path;
-	char *max_path;
-	int readlinks = 0;
-	int n;
-
-	/* Make a copy of the source path since we may need to modify it. */
-	strcpy(copy_path, path);
-	path = copy_path;
-	max_path = copy_path + MAXPATHLEN - 2;
-	/* If it's a relative pathname use getwd for starters. */
-	if (*path != '/') {
-#ifdef HAS_GETCWD
-		new_path = getcwd(new_path, MAXPATHLEN - 1);
-#else
-		new_path = getwd(new_path);
-#endif
-		if (new_path == NULL)
-		    return(NULL);
-
-		new_path += strlen(new_path);
-		if (new_path[-1] != '/')
-			*new_path++ = '/';
-	}
-	else {
-		*new_path++ = '/';
-		path++;
-	}
-	/* Expand each slash-separated pathname component. */
-	while (*path != '\0') {
-		/* Ignore stray "/". */
-		if (*path == '/') {
-			path++;
-			continue;
-		}
-		if (*path == '.') {
-			/* Ignore ".". */
-			if (path[1] == '\0' || path[1] == '/') {
-				path++;
-				continue;
-			}
-			if (path[1] == '.') {
-				if (path[2] == '\0' || path[2] == '/') {
-					path += 2;
-					/* Ignore ".." at root. */
-					if (new_path == resolved_path + 1)
-						continue;
-					/* Handle ".." by backing up. */
-					while ((--new_path)[-1] != '/')
-						;
-					continue;
-				}
-			}
-		}
-		/* Safely copy the next pathname component. */
-		while (*path != '\0' && *path != '/') {
-			if (path > max_path) {
-				errno = ENAMETOOLONG;
-				return NULL;
-			}
-			*new_path++ = *path++;
-		}
-#ifdef S_IFLNK
-		/* Protect against infinite loops. */
-		if (readlinks++ > MAX_READLINKS) {
-			errno = ELOOP;
-			return NULL;
-		}
-		/* See if latest pathname component is a symlink. */
-		*new_path = '\0';
-		n = readlink(resolved_path, link_path, MAXPATHLEN - 1);
-		if (n < 0) {
-			/* EINVAL means the file exists but isn't a symlink. */
-			if (errno != EINVAL)
-				return NULL;
-		}
-		else {
-			/* Note: readlink doesn't add the null byte. */
-			link_path[n] = '\0';
-			if (*link_path == '/')
-				/* Start over for an absolute symlink. */
-				new_path = resolved_path;
-			else
-				/* Otherwise back up over this component. */
-				while (*(--new_path) != '/')
-					;
-			/* Safe sex check. */
-			if (strlen(path) + n >= MAXPATHLEN) {
-				errno = ENAMETOOLONG;
-				return NULL;
-			}
-			/* Insert symlink contents into path. */
-			strcat(link_path, path);
-			strcpy(copy_path, link_path);
-			path = copy_path;
-		}
-#endif /* S_IFLNK */
-		*new_path++ = '/';
-	}
-	/* Delete trailing slash but don't whomp a lone slash. */
-	if (new_path != resolved_path + 1 && new_path[-1] == '/')
-		new_path--;
-	/* Make sure it's null terminated. */
-	*new_path = '\0';
-	return resolved_path;
-}
-# define HAS_REALPATH
-#endif /* WANT_REALPATH && not HAS_REALPATH */
-
-%}
-! !
-
 !UnixOperatingSystem class methodsFor:'documentation'!
 
 copyright
@@ -983,6 +648,7 @@
 "
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'initialization'!
 
 initialize
@@ -1023,6 +689,7 @@
     "Modified: / 11.12.1998 / 16:22:48 / cg"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'OS signal constants'!
 
 sigABRT
@@ -1754,6 +1421,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'error messages'!
 
 currentErrorNumber
@@ -2828,6 +2496,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'executing OS commands-implementation'!
 
 exec:aCommandPathArg withArguments:argColl environment:environmentDictionary
@@ -2899,7 +2568,7 @@
 %{  /* STACK: 16000 */
     char **argv;
     int nargs, i, id;
-    OBJ arg;
+    OBJ arg; 
 #ifdef __osx__
     char **environ = _NSGetEnviron();
 #else
@@ -3272,6 +2941,7 @@
     "Created: / 12.11.1998 / 14:39:20 / cg"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'executing OS commands-queries'!
 
 commandAndArgsForOSCommand:aCommandString
@@ -3369,6 +3039,7 @@
     "Modified: / 5.6.1998 / 19:03:32 / cg"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'file access'!
 
 closeFd:anInteger
@@ -3896,6 +3567,7 @@
     ^ self primitiveFailed
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'file access rights'!
 
 accessMaskFor:aSymbol
@@ -4038,6 +3710,7 @@
     ^ self primitiveFailed
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'file locking'!
 
 lockFD:aFileDescriptor shared:isSharedReadLock blocking:blockIfLocked
@@ -4264,6 +3937,7 @@
     ^ false
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'file queries'!
 
 caseSensitiveFilenames
@@ -5341,6 +5015,7 @@
     "Modified: / 5.6.1998 / 18:38:11 / cg"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'interrupts & signals'!
 
 defaultSignal:signalNumber
@@ -6040,6 +5715,7 @@
     "Modified: / 27.1.1998 / 20:05:59 / cg"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'ipc support'!
 
 makeBidirectionalPipe
@@ -6342,6 +6018,7 @@
     self primitiveFailed
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'misc'!
 
 closeLeftOverFiles
@@ -6422,6 +6099,7 @@
     "Modified: 22.4.1996 / 13:13:09 / cg"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'os queries'!
 
 executableFileExtensions
@@ -6467,6 +6145,25 @@
     "
 !
 
+getCodesetEncoder
+    "Initialize CodesetEncoder used to encode/decode strings passed to/from
+     the operating system (like file names, command output, environment ect.).
+
+     NOTE: DO NOT CALL this in #initialize as CharacterEncoder might not yet 
+     be initialized. Therefore this method is called from CharacterEncoder class>>
+     #initialize. Certainly a hack, but class initialization order is undefined,
+     so some sort of hack is necessary.
+
+     NOTE2: This should be called initializeCodesetEncoder but to make it consistent
+     with getCodeset it is getCodesetEncoder
+     "
+
+    Codeset isNil ifTrue:[self getCodeset].
+    CodesetEncoder := CharacterEncoder encoderFor: Codeset.
+
+    "Created: / 23-01-2013 / 09:54:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 getDomainName
     "return the domain this host is in.
      Notice:
@@ -6518,7 +6215,7 @@
 
     |resultArray error dict sz "{ Class: SmallInteger }"|
 
-%{
+%{ 
 #ifdef __osx__
     char **environ = _NSGetEnviron();
 #else
@@ -8531,6 +8228,7 @@
 
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'path queries'!
 
 decodePath:encodedPathName
@@ -8539,15 +8237,23 @@
      so the pathName has been UTF-8 decoded."
 
     "linux strings are in UTF8 (in contemporary linux versions)"
-    (encodedPathName notNil and:[Codeset == #utf8]) ifTrue:[
-	[
-	    ^ encodedPathName utf8Decoded.
-	] on:InvalidEncodingError do:[:ex|
-	    "maybe there are old filenames in ISO8859-x,
-	     just keep them untranslated"
-	].
+    encodedPathName notNil ifTrue:[
+        [
+            Codeset == #utf8 ifTrue:[
+                ^ encodedPathName utf8Decoded.
+            ].
+            "/ Codeset encoder might not yet be initialized, sigh...
+            CodesetEncoder notNil ifTrue:[
+                ^ CodesetEncoder decodeString: encodedPathName             
+            ].
+        ] on:InvalidEncodingError do:[:ex|
+            "maybe there are old filenames in ISO8859-x,
+             just keep them untranslated"
+        ].
     ].
     ^ encodedPathName
+
+    "Modified: / 23-01-2013 / 10:02:05 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 defaultSystemPath
@@ -8605,12 +8311,21 @@
      E.g. linux system calls accept single byte strings only,
      so the pathName has been UTF-8 encoded, before using it in a system call."
 
-    (pathName notNil and:[Codeset == #utf8]) ifTrue:[
-        ^ pathName utf8Encoded.
+    pathName notNil ifTrue:[
+        Codeset == #utf8 ifTrue:[
+            ^ pathName utf8Encoded
+        ].
+        "/ Codeset encoder might not yet be initialized, sigh...
+        CodesetEncoder notNil ifTrue:[
+            ^ CodesetEncoder encodeString: pathName.            
+        ].
     ].
     ^ pathName
+
+    "Modified: / 23-01-2013 / 10:00:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'private'!
 
 mountPointsFromProcFS
@@ -8643,6 +8358,7 @@
     "Created: / 12.6.1998 / 16:30:43 / cg"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'shared memory access'!
 
 shmAttach:id address:addr flags:flags
@@ -8725,6 +8441,7 @@
     "Modified: 22.4.1996 / 13:14:46 / cg"
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'socket creation'!
 
 socketAccessor
@@ -8741,6 +8458,7 @@
     ^ SocketHandle new domain:domainArg type:typeArg protocol:protocolArg
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'time and date'!
 
 computeOSTimeFromUTCYear:y month:m day:d hour:h minute:min second:s millisecond:millis
@@ -9183,6 +8901,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'users & groups'!
 
 getEffectiveGroupID
@@ -9553,6 +9272,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'waiting for events'!
 
 blockingChildProcessWait
@@ -10271,6 +9991,7 @@
     ^ self primitiveFailed
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle class methodsFor:'change & update'!
 
 update:aspect with:argument from:anObject
@@ -10290,6 +10011,7 @@
     "Created: 30.9.1997 / 12:57:35 / stefan"
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle class methodsFor:'initialization'!
 
 initialize
@@ -10304,6 +10026,7 @@
     "Modified: 30.9.1997 / 12:40:55 / stefan"
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle class methodsFor:'instance creation'!
 
 for:aFileDescriptor
@@ -10314,6 +10037,7 @@
     "Created: 30.9.1997 / 14:00:00 / stefan"
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'error handling'!
 
 error:anErrorSymbolOrErrno
@@ -10326,6 +10050,7 @@
     self primitiveFailed:anErrorSymbolOrErrno.
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'file access'!
 
 close
@@ -10340,6 +10065,7 @@
     "Modified: 30.9.1997 / 13:06:55 / stefan"
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'initialization'!
 
 for:aFileDescriptor
@@ -10365,6 +10091,7 @@
     "Modified (comment): / 16-03-2013 / 00:04:56 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'input/output'!
 
 readBytes:count into:aByteBuffer startingAt:firstIndex
@@ -10639,6 +10366,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'misc functions'!
 
 nextError
@@ -10795,6 +10523,7 @@
 
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'private-accessing'!
 
 fileDescriptor
@@ -10821,6 +10550,7 @@
 
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'queries'!
 
 canReadWithoutBlocking
@@ -10936,6 +10666,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'registering'!
 
 register
@@ -10968,6 +10699,7 @@
     "Modified (comment): / 16-03-2013 / 00:04:38 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'releasing'!
 
 invalidate
@@ -10980,6 +10712,7 @@
     "Modified: 30.9.1997 / 12:42:16 / stefan"
 ! !
 
+
 !UnixOperatingSystem::FileDescriptorHandle methodsFor:'waiting'!
 
 readWaitWithTimeoutMs:timeout
@@ -11048,6 +10781,7 @@
     ^ canWrite not
 ! !
 
+
 !UnixOperatingSystem::FilePointerHandle methodsFor:'release'!
 
 closeFile
@@ -11064,6 +10798,7 @@
 
 ! !
 
+
 !UnixOperatingSystem::FileStatusInfo class methodsFor:'instance creation'!
 
 type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT path:lP numLinks:nL
@@ -11071,6 +10806,7 @@
 	type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT path:lP numLinks:nL
 ! !
 
+
 !UnixOperatingSystem::FileStatusInfo methodsFor:'accessing'!
 
 accessTime
@@ -11161,6 +10897,7 @@
     ^ uid
 ! !
 
+
 !UnixOperatingSystem::FileStatusInfo methodsFor:'accessing-vms'!
 
 fixedHeaderSize
@@ -11193,6 +10930,7 @@
     ^ nil
 ! !
 
+
 !UnixOperatingSystem::FileStatusInfo methodsFor:'backward compatibility'!
 
 accessed
@@ -11224,6 +10962,7 @@
     ^ self statusChangeTime
 ! !
 
+
 !UnixOperatingSystem::FileStatusInfo methodsFor:'private-accessing'!
 
 type:t mode:m uid:u gid:g size:s id:i accessed:aT modified:mT statusChanged:sT path:lP numLinks:nL
@@ -11240,6 +10979,7 @@
     numLinks := nL.
 ! !
 
+
 !UnixOperatingSystem::FileStatusInfo methodsFor:'queries-access'!
 
 isGroupExecutable
@@ -11314,6 +11054,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem::FileStatusInfo methodsFor:'queries-type'!
 
 isBlockSpecial
@@ -11348,6 +11089,7 @@
     ^ type == #unknown
 ! !
 
+
 !UnixOperatingSystem::MountInfo methodsFor:'accessing'!
 
 mountPointPath
@@ -11365,6 +11107,7 @@
     attributeString := attributeStringArg.
 ! !
 
+
 !UnixOperatingSystem::MountInfo methodsFor:'printing'!
 
 printOn:aStream
@@ -11373,12 +11116,14 @@
 	nextPutAll:mountPointPath.
 ! !
 
+
 !UnixOperatingSystem::MountInfo methodsFor:'queries'!
 
 isRemote
     ^ fsType = 'nfs'
 ! !
 
+
 !UnixOperatingSystem::OSProcessStatus class methodsFor:'documentation'!
 
 documentation
@@ -11405,6 +11150,7 @@
 "
 ! !
 
+
 !UnixOperatingSystem::OSProcessStatus class methodsFor:'instance creation'!
 
 pid:pid status:status code:code core:core
@@ -11425,6 +11171,7 @@
     "Modified: 30.4.1996 / 18:25:05 / cg"
 ! !
 
+
 !UnixOperatingSystem::OSProcessStatus methodsFor:'accessing'!
 
 code
@@ -11463,6 +11210,7 @@
     "Modified: 30.4.1996 / 18:26:54 / cg"
 ! !
 
+
 !UnixOperatingSystem::OSProcessStatus methodsFor:'initialization'!
 
 pid:newPid status:newStatus code:newCode core:newCore
@@ -11474,6 +11222,7 @@
     "Created: 28.12.1995 / 14:18:22 / stefan"
 ! !
 
+
 !UnixOperatingSystem::OSProcessStatus methodsFor:'printing & storing'!
 
 printOn:aStream
@@ -11485,6 +11234,7 @@
     aStream nextPut:$).
 ! !
 
+
 !UnixOperatingSystem::OSProcessStatus methodsFor:'private-OS interface'!
 
 code:something
@@ -11520,6 +11270,7 @@
     "Created: 28.12.1995 / 14:05:07 / stefan"
 ! !
 
+
 !UnixOperatingSystem::OSProcessStatus methodsFor:'queries'!
 
 couldNotExecute
@@ -11548,6 +11299,7 @@
     "Modified: 28.12.1995 / 14:13:41 / stefan"
 ! !
 
+
 !UnixOperatingSystem::SocketHandle class methodsFor:'constants'!
 
 protocolCodeOf:aNameOrNumber
@@ -11639,6 +11391,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem::SocketHandle class methodsFor:'initialization'!
 
 reinitialize
@@ -11647,6 +11400,7 @@
     ProtocolCache := nil.
 ! !
 
+
 !UnixOperatingSystem::SocketHandle class methodsFor:'queries'!
 
 XXgetAddressInfo:hostName serviceName:serviceNameArg domain:domainArg type:typeArg protocol:protoArg flags:flags
@@ -12647,6 +12401,7 @@
     ^ result.
 ! !
 
+
 !UnixOperatingSystem::SocketHandle methodsFor:'accepting'!
 
 acceptWithPeerAddressBuffer:peerOrNil
@@ -12720,6 +12475,7 @@
     ^ self class for:newFd
 ! !
 
+
 !UnixOperatingSystem::SocketHandle methodsFor:'binding'!
 
 bindTo:socketAddress
@@ -12774,6 +12530,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem::SocketHandle methodsFor:'connecting'!
 
 cancelConnect
@@ -12896,6 +12653,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem::SocketHandle methodsFor:'datagram transmission'!
 
 receiveFrom:socketAddress buffer:aDataBuffer start:startIndex for:nBytes flags:flags
@@ -13132,6 +12890,7 @@
     ^ self error:error.
 ! !
 
+
 !UnixOperatingSystem::SocketHandle methodsFor:'initialization'!
 
 domain:domainArg type:typeArg protocol:protocolArg
@@ -13217,6 +12976,7 @@
     "
 ! !
 
+
 !UnixOperatingSystem::SocketHandle methodsFor:'misc'!
 
 getOptionsLevel:level name:name
@@ -13408,6 +13168,7 @@
     ^ nil.
 ! !
 
+
 !UnixOperatingSystem::SocketHandle methodsFor:'queries'!
 
 getNameInto:socketAddress
@@ -13485,6 +13246,7 @@
     ^ nil
 ! !
 
+
 !UnixOperatingSystem class methodsFor:'documentation'!
 
 version
@@ -13493,8 +13255,13 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic/UnixOperatingSystem.st,v 1.307 2013-03-19 12:59:14 stefan Exp $'
+!
+
+version_HG
+
+    ^ '$Changeset: <not expanded> $'
 ! !
 
 
+UnixOperatingSystem::FileDescriptorHandle initialize!
 UnixOperatingSystem initialize!
-UnixOperatingSystem::FileDescriptorHandle initialize!
--- a/UnorderedNumbersError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UnorderedNumbersError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -40,16 +40,22 @@
 "
 ! !
 
+
 !UnorderedNumbersError class methodsFor:'initialization'!
 
 initialize
     NotifierString := 'unordered'.
 ! !
 
+
 !UnorderedNumbersError class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/UnorderedNumbersError.st,v 1.5 2013-03-13 23:44:03 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: UnorderedNumbersError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 
--- a/UnprotectedExternalBytes.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UnprotectedExternalBytes.st	Thu Mar 28 12:21:50 2013 +0000
@@ -1,3 +1,14 @@
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
 "{ Package: 'stx:libbasic' }"
 
 ExternalBytes subclass:#UnprotectedExternalBytes
@@ -9,6 +20,20 @@
 
 !UnprotectedExternalBytes class methodsFor:'documentation'!
 
+copyright
+"
+ COPYRIGHT (c) 2006 by eXept Software AG
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
 documentation
 "
     This is just a factory to generate ExternalBytes.
@@ -43,5 +68,12 @@
 !UnprotectedExternalBytes class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UnprotectedExternalBytes.st,v 1.1 2002-04-09 15:23:15 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UnprotectedExternalBytes.st,v 1.1 2002/04/09 15:23:15 stefan Exp $'
+!
+
+version_SVN
+    ^ '$Id: UnprotectedExternalBytes.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/UserConfirmation.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UserConfirmation.st	Thu Mar 28 12:21:50 2013 +0000
@@ -61,6 +61,7 @@
 "
 ! !
 
+
 !UserConfirmation methodsFor:'accessing'!
 
 aspect
@@ -104,6 +105,7 @@
     defaultAnswer := aBooleanOrNil
 ! !
 
+
 !UserConfirmation methodsFor:'default actions'!
 
 defaultAction
@@ -150,6 +152,7 @@
     "
 ! !
 
+
 !UserConfirmation class methodsFor:'documentation'!
 
 version
@@ -158,5 +161,9 @@
 
 version_CVS
     ^ '$Header: /cvs/stx/stx/libbasic/UserConfirmation.st,v 1.7 2013-03-25 14:00:49 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: UserConfirmation.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
--- a/UserInformation.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UserInformation.st	Thu Mar 28 12:21:50 2013 +0000
@@ -63,7 +63,14 @@
 !UserInformation class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UserInformation.st,v 1.4 2008-10-04 08:42:26 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UserInformation.st,v 1.4 2008/10/04 08:42:26 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: UserInformation.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 UserInformation initialize!
+
+
+
--- a/UserPreferences.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/UserPreferences.st	Thu Mar 28 12:21:50 2013 +0000
@@ -860,7 +860,18 @@
 !UserPreferences methodsFor:'accessing-pref''d tools'!
 
 changeSetBrowserClass
-    "using old or jan's changeSet browser for package diffs"
+
+    | class className |
+
+    className := self at: #changeSetBrowserClassName ifAbsent:[nil].
+    className notNil ifTrue:[
+        class := Smalltalk at: className asSymbol.
+        class notNil ifTrue:[ ^ class ].
+    ].
+
+    "Original code"
+    ^ ChangeSetBrowser.
+    "/^ Tools::ChangeSetBrowser2 ? ChangeSetBrowser
 
     self useNewChangeSetBrowser ifTrue:[
         ^ Tools::ChangeSetBrowser2 ? ChangeSetBrowser
@@ -873,18 +884,54 @@
 
     "Created: / 01-07-2011 / 16:33:13 / cg"
     "Modified: / 25-07-2011 / 12:21:42 / sr"
-    "Modified (comment): / 26-07-2012 / 15:07:43 / cg"
+    "Modified: / 25-01-2012 / 17:11:08 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+changeSetBrowserClass: aClass
+
+    self at: #changeSetBrowserClassName put: aClass name.
+
+    "
+        UserPreferences current changeSetBrowserClass
+        UserPreferences current changeSetBrowserClass: Tools::ChangeSetBrowser2.
+        UserPreferences current changeSetBrowserClass: ChangeSetBrowser.
+    "
+
+    "Created: / 25-01-2012 / 17:08:45 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 changesBrowserClass
     "the browser to be used for the changeFile"
 
+    | class className |
+
+    className := self at: #changesBrowserClassName ifAbsent:[nil].
+    className notNil ifTrue:[
+        class := Smalltalk at: className asSymbol.
+        class notNil ifTrue:[ ^ class ].
+    ].
+
+    "/ Old code
     self useNewChangesBrowser ifTrue:[
         ^ (NewChangesBrowser ? ChangesBrowser)
     ].
     ^ ChangesBrowser
 
     "Created: / 17-10-1998 / 14:37:46 / cg"
+    "Modified: / 25-01-2012 / 17:11:55 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
+changesBrowserClass: aClass
+
+    self at: #changesBrowserClassName put: aClass name.
+
+    "
+        UserPreferences current changesBrowserClass
+        UserPreferences current changesBrowserClass: Tools::ChangeSetBrowser2.
+        UserPreferences current changesBrowserClass: ChangeSetBrowser.
+    "
+
+    "Created: / 25-01-2012 / 17:12:15 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
 externalDiffCommandTemplate
--- a/WeakValueIdentityDictionary.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/WeakValueIdentityDictionary.st	Thu Mar 28 12:21:50 2013 +0000
@@ -251,5 +251,8 @@
 !WeakValueIdentityDictionary class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WeakValueIdentityDictionary.st,v 1.4 2006-03-06 10:04:38 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/WeakValueIdentityDictionary.st,v 1.4 2006/03/06 10:04:38 cg Exp $'
 ! !
+
+
+
--- a/WriteError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/WriteError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 StreamError subclass:#WriteError
@@ -38,5 +37,12 @@
 !WriteError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WriteError.st,v 1.2 2005-02-02 11:04:48 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/WriteError.st,v 1.2 2005/02/02 11:04:48 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: WriteError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
+
+
+
--- a/WrongNumberOfArgumentsError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/WrongNumberOfArgumentsError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,7 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
 "{ Package: 'stx:libbasic' }"
 
 ArgumentError subclass:#WrongNumberOfArgumentsError
@@ -56,7 +55,14 @@
 !WrongNumberOfArgumentsError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WrongNumberOfArgumentsError.st,v 1.5 2003-12-05 15:47:45 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/WrongNumberOfArgumentsError.st,v 1.5 2003/12/05 15:47:45 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: WrongNumberOfArgumentsError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 WrongNumberOfArgumentsError initialize!
+
+
+
--- a/WrongProceedabilityError.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/WrongProceedabilityError.st	Thu Mar 28 12:21:50 2013 +0000
@@ -9,9 +9,6 @@
  other person.  No title to or ownership of the software is
  hereby transferred.
 "
-
-
-
 "{ Package: 'stx:libbasic' }"
 
 SignalError subclass:#WrongProceedabilityError
@@ -67,7 +64,14 @@
 !WrongProceedabilityError class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/WrongProceedabilityError.st,v 1.4 2003-08-29 19:14:38 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/WrongProceedabilityError.st,v 1.4 2003/08/29 19:14:38 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: WrongProceedabilityError.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 WrongProceedabilityError initialize!
+
+
+
--- a/ZeroDivide.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/ZeroDivide.st	Thu Mar 28 12:21:50 2013 +0000
@@ -65,12 +65,14 @@
 "
 ! !
 
+
 !ZeroDivide class methodsFor:'initialization'!
 
 initialize
     NotifierString := 'division by zero'.
 ! !
 
+
 !ZeroDivide methodsFor:'accessing'!
 
 defaultResumeValue
@@ -123,10 +125,15 @@
     "
 ! !
 
+
 !ZeroDivide class methodsFor:'documentation'!
 
 version
     ^ '$Header: /cvs/stx/stx/libbasic/ZeroDivide.st,v 1.8 2013-01-25 17:19:34 cg Exp $'
+!
+
+version_SVN
+    ^ '$Id: ZeroDivide.st 10761 2012-01-19 11:46:00Z vranyj1 $'
 ! !
 
 
--- a/bc.mak	Wed Mar 27 20:36:15 2013 +0100
+++ b/bc.mak	Thu Mar 28 12:21:50 2013 +0000
@@ -103,6 +103,7 @@
 $(OUTDIR)OSProcess.$(O) OSProcess.$(H): OSProcess.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ObjectMemory.$(O) ObjectMemory.$(H): ObjectMemory.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)PackageId.$(O) PackageId.$(H): PackageId.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
+$(OUTDIR)PolymorphicInlineCache.$(O) PolymorphicInlineCache.$(H): PolymorphicInlineCache.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ProcessorScheduler.$(O) ProcessorScheduler.$(H): ProcessorScheduler.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)ProgrammingLanguage.$(O) ProgrammingLanguage.$(H): ProgrammingLanguage.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
 $(OUTDIR)Project.$(O) Project.$(H): Project.st $(INCLUDE_TOP)\stx\libbasic\Object.$(H) $(STCHDR)
@@ -397,3 +398,12 @@
 $(OUTDIR)Win32Process.$(O) Win32Process.$(H): Win32Process.st $(STCHDR)
 
 # ENDMAKEDEPEND --- do not remove this line
+
+# **Must be at end**
+
+# Enforce recompilation of package definition class if Mercurial working
+# copy state changes. Together with --guessVersion it ensures that package
+# definition class always contains correct binary revision string.
+!IFDEF HGROOT
+$(OUTDIR)stx_libbasic.$(O): $(HGROOT)\.hg\dirstate
+!ENDIF
\ No newline at end of file
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/lcmake.bat	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,8 @@
+@REM -------
+@REM make using lcc compiler
+@REM type lcmake, and wait...
+@REM do not edit - automatically generated from ProjectDefinition
+@REM -------
+make.exe -N -f bc.mak USELCC=1 %1 %2
+
+
--- a/libbasic.rc	Wed Mar 27 20:36:15 2013 +0100
+++ b/libbasic.rc	Thu Mar 28 12:21:50 2013 +0000
@@ -4,7 +4,7 @@
 //
 VS_VERSION_INFO VERSIONINFO
   FILEVERSION     6,2,1,112
-  PRODUCTVERSION  6,2,2,0
+  PRODUCTVERSION  6,2,3,0
 #if (__BORLANDC__)
   FILEFLAGSMASK   VS_FF_DEBUG | VS_FF_PRERELEASE
   FILEFLAGS       VS_FF_PRERELEASE | VS_FF_SPECIALBUILD
@@ -24,7 +24,7 @@
       VALUE "InternalName", "stx:libbasic\0"
       VALUE "LegalCopyright", "Copyright Claus Gittinger 1988-2012\nCopyright eXept Software AG 1998-2013\0"
       VALUE "ProductName", "Smalltalk/X\0"
-      VALUE "ProductVersion", "6.2.2.0\0"
+      VALUE "ProductVersion", "6.2.3.0\0"
       VALUE "ProductDate", "Tue, 19 Mar 2013 13:31:56 GMT\0"
     END
 
--- a/mingwmake.bat	Wed Mar 27 20:36:15 2013 +0100
+++ b/mingwmake.bat	Thu Mar 28 12:21:50 2013 +0000
@@ -3,6 +3,10 @@
 @REM type mingwmake, and wait...
 @REM do not edit - automatically generated from ProjectDefinition
 @REM -------
+@SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
 
 @pushd ..\rules
 @call find_mingw.bat
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/not_delivered/.cvsignore	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,2 @@
+*.bad
+*.new
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/not_delivered/SysDict.st	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,316 @@
+"
+ COPYRIGHT (c) 1994 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+Collection subclass:#SystemDictionary
+       instanceVariableNames:'sysId'
+       classVariableNames:''
+       poolDictionaries:''
+       category:'System-Support'
+!
+
+!SystemDictionary class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1994 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic/not_delivered/SysDict.st,v 1.1 1996/09/12 01:05:30 cg Exp $'
+!
+
+documentation
+"
+    SystemDictionaries are nameSpaces, which are also known in the c-world
+    somehow (i.e. names found in SystemDictionaries may also be known as
+    a c-global).
+
+    As you will notice, this is NOT a Dictionary
+     - my implementation of globals is totally different
+       (due to the need to be able to access globals from c-code as well).
+    However, it provides the known enumeration protocol.
+
+    Instance variables:
+	sysId           <SmallInteger>  the dictionaries id
+"
+! !
+
+!SystemDictionary methodsFor:'accessing'!
+
+at:aKey
+    "retrieve the value stored under aKey, which must be some kind of symbol.
+     Return nil if not present."
+
+%{  /* NOCONTEXT */
+    extern OBJ _SYSDICT_GET();
+
+    if (__isSmallInteger(__INST(sysId))) {
+	RETURN ( _SYSDICT_GET(__intVal(__INST(sysId)), aKey) );
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+at:aKey ifAbsent:aBlock
+    "retrieve the value stored under aKey.
+     If there is none stored this key, return the value of
+     the evaluation of aBlock"
+
+    (self includesKey:aKey) ifTrue:[
+	^ self at:aKey
+    ].
+    ^ aBlock value
+!
+
+at:aKey put:aValue
+    "store the argument aValue under aKey, which must be some kind of symbol."
+
+%{  /* NOCONTEXT */
+    if (__isSmallInteger(__INST(sysId))) {
+	_SYSDICT_SET(__intVal(__INST(sysId)), aKey, aValue, (OBJ *)0);
+	RETURN (aValue);
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+removeKey:aKey
+    "remove the argument from the globals dictionary"
+
+%{  /* NOCONTEXT */
+    extern OBJ _SYSDICT_REMOVE();
+
+    if (__isSmallInteger(__INST(sysId))) {
+	RETURN ( _SYSDICT_REMOVE(__intVal(__INST(sysId)), aKey) );
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+includesKey:aKey
+    "return true, if the key is known"
+
+%{  /* NOCONTEXT */
+    extern OBJ _SYSDICT_KEYKNOWN();
+
+    if (__isSmallInteger(__INST(sysId))) {
+	RETURN ( _SYSDICT_KEYKNOWN(__intVal(__INST(sysId)), aKey) );
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+keyAtValue:anObject
+    "return the symbol under which anObject is stored - or nil"
+
+    self allKeysDo:[:aKey |
+	(self at:aKey) == anObject ifTrue:[^ aKey]
+    ]
+
+    "Smalltalk keyAtValue:Object"
+!
+
+keys
+    "return a collection with all keys in the Smalltalk dictionary"
+
+    |keys|
+
+    keys := IdentitySet new.
+    self allKeysDo:[:k | keys add:k].
+    ^ keys
+! !
+
+!SystemDictionary class methodsFor:'copying'!
+
+shallowCopy
+    "redefine copy - there is only one instance of each dictionary"
+
+    ^ self
+!
+
+simpleDeepCopy
+    "redefine copy - there is only one instance of each dictionary"
+
+    ^ self
+!
+
+deepCopyUsing:aDictionary
+    "redefine copy - there is only one instance of each dictionary"
+
+    ^ self
+!
+
+deepCopy
+    "redefine copy - there is only one instance of each dictionary"
+
+    ^ self
+! !
+
+!SystemDictionary methodsFor:'inspecting'!
+
+inspect
+    "redefined to launch a DictionaryInspector on the receiver
+     (instead of the default InspectorView)."
+
+    DictionaryInspectorView isNil ifTrue:[
+	super inspect
+    ] ifFalse:[
+	DictionaryInspectorView openOn:self
+    ]
+! !
+
+!SystemDictionary methodsFor:'enumeration'!
+
+do:aBlock
+    "evaluate the argument, aBlock for all values in the dictionary"
+%{
+    if (__isSmallInteger(__INST(sysId))) {
+	_SYSDICT_DO(__intVal(__INST(sysId)), &aBlock COMMA_CON);
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+
+    "
+     Smalltalk do:[:value | value class name printNL]
+    "
+!
+
+allKeysDo:aBlock
+    "evaluate the argument, aBlock for all keys in the dictionary"
+%{
+    if (__isSmallInteger(__INST(sysId))) {
+	_SYSDICT_KEYSDO(__intVal(__INST(sysId)), &aBlock COMMA_CON);
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+
+    "
+     Smalltalk allKeysDo:[:key | key printNL]
+    "
+!
+
+associationsDo:aBlock
+    "evaluate the argument, aBlock for all key/value pairs 
+     in the dictionary"
+
+    self allKeysDo:[:aKey |
+	aBlock value:(aKey -> (self at:aKey))
+    ]
+
+    "
+     Smalltalk associationsDo:[:assoc | assoc printNL]
+    "
+!
+
+keysAndValuesDo:aBlock
+    "evaluate the two-arg block, aBlock for all keys and values"
+
+    self allKeysDo:[:aKey |
+	aBlock value:aKey value:(self at:aKey)
+    ]
+! !
+
+!SystemDictionary methodsFor:'queries'!
+
+cellAt:aKey
+    "return the address of a global cell
+     - used internally for compiler only"
+
+%{  /* NOCONTEXT */
+    extern OBJ _SYSDICT_GETCELL();
+
+    if (__isSmallInteger(__INST(sysId))) {
+	RETURN ( _SYSDICT_GETCELL(__intVal(__INST(sysId)), aKey) );
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+references:anObject
+    "return true, if I refer to the argument, anObject
+     must be reimplemented since systemDictionaries are no real collections."
+
+    self do:[:o |
+	(o == anObject) ifTrue:[^ true]
+    ].
+    ^ false
+! !
+
+!SystemDictionary class methodsFor: 'binary storage'!
+
+addGlobalsTo:globalDictionary manager: manager
+    |pools|
+
+    pools := Set new.
+    self associationsDo:[:assoc |
+	|value|
+
+	value := assoc value.
+	value == self ifFalse:[
+	    value isClass ifTrue:[
+		value addGlobalsTo:globalDictionary manager:manager.
+		pools addAll:value sharedPools
+	    ] ifFalse:[
+		globalDictionary at:assoc put:self
+	    ].
+	    value isNil ifFalse:[
+		globalDictionary at:value put:self
+	    ]
+	]
+    ].
+
+    pools do:[:poolDictionary|
+	poolDictionary addGlobalsTo:globalDictionary manager:manager
+    ]
+!
+
+storeBinaryDefinitionOf:anObject on:stream manager:manager
+    |string|
+
+    anObject class == Association ifTrue:[
+	string := 'Smalltalk associationAt:', anObject key storeString
+    ] ifFalse: [
+	string := 'Smalltalk at:', (self keyAtValue: anObject) storeString
+    ].
+    stream nextNumber:2 put:string size.
+    string do:[:char | stream nextPut:char asciiValue]
+! !
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/not_delivered/SystemDictionary.st	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,321 @@
+"
+ COPYRIGHT (c) 1994 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+Collection subclass:#SystemDictionary
+       instanceVariableNames:'sysId'
+       classVariableNames:''
+       poolDictionaries:''
+       category:'System-Support'
+!
+
+!SystemDictionary class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1994 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic/not_delivered/SysDict.st,v 1.1 1996/09/12 01:05:30 cg Exp $'
+!
+
+documentation
+"
+    SystemDictionaries are nameSpaces, which are also known in the c-world
+    somehow (i.e. names found in SystemDictionaries may also be known as
+    a c-global).
+
+    As you will notice, this is NOT a Dictionary
+     - my implementation of globals is totally different
+       (due to the need to be able to access globals from c-code as well).
+    However, it provides the known enumeration protocol.
+
+    Instance variables:
+	sysId           <SmallInteger>  the dictionaries id
+"
+! !
+
+!SystemDictionary methodsFor:'accessing'!
+
+at:aKey
+    "retrieve the value stored under aKey, which must be some kind of symbol.
+     Return nil if not present."
+
+%{  /* NOCONTEXT */
+    extern OBJ _SYSDICT_GET();
+
+    if (__isSmallInteger(__INST(sysId))) {
+	RETURN ( _SYSDICT_GET(__intVal(__INST(sysId)), aKey) );
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+at:aKey ifAbsent:aBlock
+    "retrieve the value stored under aKey.
+     If there is none stored this key, return the value of
+     the evaluation of aBlock"
+
+    (self includesKey:aKey) ifTrue:[
+	^ self at:aKey
+    ].
+    ^ aBlock value
+!
+
+at:aKey put:aValue
+    "store the argument aValue under aKey, which must be some kind of symbol."
+
+%{  /* NOCONTEXT */
+    if (__isSmallInteger(__INST(sysId))) {
+	_SYSDICT_SET(__intVal(__INST(sysId)), aKey, aValue, (OBJ *)0);
+	RETURN (aValue);
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+removeKey:aKey
+    "remove the argument from the globals dictionary"
+
+%{  /* NOCONTEXT */
+    extern OBJ _SYSDICT_REMOVE();
+
+    if (__isSmallInteger(__INST(sysId))) {
+	RETURN ( _SYSDICT_REMOVE(__intVal(__INST(sysId)), aKey) );
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+includesKey:aKey
+    "return true, if the key is known"
+
+%{  /* NOCONTEXT */
+    extern OBJ _SYSDICT_KEYKNOWN();
+
+    if (__isSmallInteger(__INST(sysId))) {
+	RETURN ( _SYSDICT_KEYKNOWN(__intVal(__INST(sysId)), aKey) );
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+keyAtValue:anObject
+    "return the symbol under which anObject is stored - or nil"
+
+    self allKeysDo:[:aKey |
+	(self at:aKey) == anObject ifTrue:[^ aKey]
+    ]
+
+    "Smalltalk keyAtValue:Object"
+!
+
+keys
+    "return a collection with all keys in the Smalltalk dictionary"
+
+    |keys|
+
+    keys := IdentitySet new.
+    self allKeysDo:[:k | keys add:k].
+    ^ keys
+! !
+
+!SystemDictionary class methodsFor:'copying'!
+
+shallowCopy
+    "redefine copy - there is only one instance of each dictionary"
+
+    ^ self
+!
+
+simpleDeepCopy
+    "redefine copy - there is only one instance of each dictionary"
+
+    ^ self
+!
+
+deepCopyUsing:aDictionary
+    "redefine copy - there is only one instance of each dictionary"
+
+    ^ self
+!
+
+deepCopy
+    "redefine copy - there is only one instance of each dictionary"
+
+    ^ self
+! !
+
+!SystemDictionary methodsFor:'inspecting'!
+
+inspect
+    "redefined to launch a DictionaryInspector on the receiver
+     (instead of the default InspectorView)."
+
+    DictionaryInspectorView isNil ifTrue:[
+	super inspect
+    ] ifFalse:[
+	DictionaryInspectorView openOn:self
+    ]
+! !
+
+!SystemDictionary methodsFor:'enumeration'!
+
+do:aBlock
+    "evaluate the argument, aBlock for all values in the dictionary"
+%{
+    if (__isSmallInteger(__INST(sysId))) {
+	_SYSDICT_DO(__intVal(__INST(sysId)), &aBlock COMMA_CON);
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+
+    "
+     Smalltalk do:[:value | value class name printNL]
+    "
+!
+
+allKeysDo:aBlock
+    "evaluate the argument, aBlock for all keys in the dictionary"
+%{
+    if (__isSmallInteger(__INST(sysId))) {
+	_SYSDICT_KEYSDO(__intVal(__INST(sysId)), &aBlock COMMA_CON);
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+
+    "
+     Smalltalk allKeysDo:[:key | key printNL]
+    "
+!
+
+associationsDo:aBlock
+    "evaluate the argument, aBlock for all key/value pairs 
+     in the dictionary"
+
+    self allKeysDo:[:aKey |
+	aBlock value:(aKey -> (self at:aKey))
+    ]
+
+    "
+     Smalltalk associationsDo:[:assoc | assoc printNL]
+    "
+!
+
+keysAndValuesDo:aBlock
+    "evaluate the two-arg block, aBlock for all keys and values"
+
+    self allKeysDo:[:aKey |
+	aBlock value:aKey value:(self at:aKey)
+    ]
+! !
+
+!SystemDictionary methodsFor:'queries'!
+
+cellAt:aKey
+    "return the address of a global cell
+     - used internally for compiler only"
+
+%{  /* NOCONTEXT */
+    extern OBJ _SYSDICT_GETCELL();
+
+    if (__isSmallInteger(__INST(sysId))) {
+	RETURN ( _SYSDICT_GETCELL(__intVal(__INST(sysId)), aKey) );
+    }
+%}.
+    "
+     the receiver is not a valid systemDictionary
+    "
+    self pimitiveFailed
+!
+
+references:anObject
+    "return true, if I refer to the argument, anObject
+     must be reimplemented since systemDictionaries are no real collections."
+
+    self do:[:o |
+	(o == anObject) ifTrue:[^ true]
+    ].
+    ^ false
+! !
+
+!SystemDictionary class methodsFor: 'binary storage'!
+
+addGlobalsTo:globalDictionary manager: manager
+    |pools|
+
+    pools := Set new.
+    self associationsDo:[:assoc |
+	|value|
+
+	value := assoc value.
+	value == self ifFalse:[
+	    value isClass ifTrue:[
+		value addGlobalsTo:globalDictionary manager:manager.
+		pools addAll:value sharedPools
+	    ] ifFalse:[
+		globalDictionary at:assoc put:self
+	    ].
+	    value isNil ifFalse:[
+		globalDictionary at:value put:self
+	    ]
+	]
+    ].
+
+    pools do:[:poolDictionary|
+	poolDictionary addGlobalsTo:globalDictionary manager:manager
+    ]
+!
+
+storeBinaryDefinitionOf:anObject on:stream manager:manager
+    |string|
+
+    anObject class == Association ifTrue:[
+	string := 'Smalltalk associationAt:', anObject key storeString
+    ] ifFalse: [
+	string := 'Smalltalk at:', (self keyAtValue: anObject) storeString
+    ].
+    stream nextNumber:2 put:string size.
+    string do:[:char | stream nextPut:char asciiValue]
+! !
+
+
+
+
+
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/not_delivered/VMBehavior.st	Thu Mar 28 12:21:50 2013 +0000
@@ -0,0 +1,615 @@
+"
+ COPYRIGHT (c) 1995 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+
+Object subclass:#VMBehavior
+	instanceVariableNames:'superclass flags selectorArray methodArray'
+	classVariableNames:''
+	poolDictionaries:''
+	category:'Kernel-Classes'
+!
+
+!VMBehavior class methodsFor:'documentation'!
+
+copyright
+"
+ COPYRIGHT (c) 1995 by Claus Gittinger
+	      All Rights Reserved
+
+ This software is furnished under a license and may be used
+ only in accordance with the terms of that license and with the
+ inclusion of the above copyright notice.   This software may not
+ be provided or otherwise made available to, or used by, any
+ other person.  No title to or ownership of the software is
+ hereby transferred.
+"
+!
+
+documentation
+"
+    This class describes what the VM considers to be a classLike object.
+    Every class in the system inherits from VMBehavior (via Behavior, Class, ClassDescription).
+
+    In contrast to Behavior (which describes smalltalk behavior), the things defined
+    here are valid for all objects for which the VM can do a method lookup.
+    In theory, you can create totally different object systems on top of VMBehavior.
+    This class is purely abstract - therefore, no smalltalk behavior is defined here.
+
+    This is certainly not for normal applications.
+
+    Instance variables:
+
+	superclass        <Class>           where lookup continues when a selector is not
+					    found in the selector array
+					    (i.e. the superclass in Smalltalk terms)
+
+	selectorArray     <Array of Symbol> the selectors for which inst-methods are defined here
+
+	methodArray       <Array of Method> the inst-methods corresponding to the selectors
+
+	flags             <SmallInteger>    special flag bits coded in a number
+					    not for application use
+
+    flag bits (see stc.h):
+
+    NOTICE: layout known by compiler and runtime system; be careful when changing
+"
+! !
+
+!VMBehavior class methodsFor:'initialization'!
+
+initialize
+    self == VMBehavior ifTrue:[
+        self flags:(self flagBehavior).
+    ]
+
+    "
+      self initialize
+    "
+! !
+
+!VMBehavior class methodsFor:'flag bit constants'!
+
+flagBehavior
+    "return the flag code which marks Behavior-like instances.
+     You have to check this single bit in the flag value when
+     checking for behaviors."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(BEHAVIOR_INSTS) );
+%}
+
+    "consistency check:
+     all class-entries must be behaviors;
+     all behaviors must be flagged so (in its class's flags)
+     (otherwise, VM will bark)
+     all non-behaviors may not be flagged
+
+     |bit|
+     bit := Class flagBehavior.
+
+     ObjectMemory allObjectsDo:[:o|
+       o isBehavior ifTrue:[
+	 (o class flags bitTest:bit) ifFalse:[
+	     self halt
+	 ].
+       ] ifFalse:[
+	 (o class flags bitTest:bit) ifTrue:[
+	     self halt
+	 ].
+       ].
+       o class isBehavior ifFalse:[
+	 self halt
+       ] ifTrue:[
+	 (o class class flags bitTest:bit) ifFalse:[
+	     self halt
+	 ]
+       ]
+     ]
+    "
+!
+
+flagBlock
+    "return the flag code which marks Block-like instances.
+     You have to check this single bit in the flag value when
+     checking for blocks."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(BLOCK_INSTS) );
+%}
+!
+
+flagBlockContext
+    "return the flag code which marks BlockContext-like instances.
+     You have to check this single bit in the flag value when
+     checking for blockContexts."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(BCONTEXT_INSTS) );
+%}
+!
+
+flagBytes
+    "return the flag code for byte-valued indexed instances.
+     You have to mask the flag value with indexMask when comparing
+     it with flagBytes."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(BYTEARRAY) );
+%}
+    "
+     Behavior flagBytes    
+    "
+!
+
+flagContext
+    "return the flag code which marks Context-like instances.
+     You have to check this single bit in the flag value when
+     checking for contexts."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(CONTEXT_INSTS) );
+%}
+!
+
+flagDoubles
+    "return the flag code for double-valued indexed instances (i.e. 8-byte reals).
+     You have to mask the flag value with indexMask when comparing
+     it with flagDoubles."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(DOUBLEARRAY) );
+%}
+    "
+     Behavior flagDoubles    
+    "
+!
+
+flagFloat
+    "return the flag code which marks Float-like instances.
+     You have to check this single bit in the flag value when
+     checking for floats."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(FLOAT_INSTS) );
+%}
+!
+
+flagFloats
+    "return the flag code for float-valued indexed instances (i.e. 4-byte reals).
+     You have to mask the flag value with indexMask when comparing
+     it with flagFloats."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(FLOATARRAY) );
+%}
+    "
+     Behavior flagFloats    
+    "
+!
+
+flagLongs
+    "return the flag code for long-valued indexed instances (i.e. 4-byte).
+     You have to mask the flag value with indexMask when comparing
+     it with flagLongs."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(LONGARRAY) );
+%}
+    "
+     Behavior flagLongs    
+    "
+!
+
+flagMethod
+    "return the flag code which marks Method-like instances.
+     You have to check this single bit in the flag value when
+     checking for methods."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(METHOD_INSTS) );
+%}
+!
+
+flagNotIndexed
+    "return the flag code for non-indexed instances.
+     You have to mask the flag value with indexMask when comparing
+     it with flagNotIndexed."
+
+    ^ 0
+!
+
+flagPointers
+    "return the flag code for pointer indexed instances (i.e. Array of object).
+     You have to mask the flag value with indexMask when comparing
+     it with flagPointers."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(POINTERARRAY) );
+%}
+    "
+     Behavior flagPointers    
+    "
+!
+
+flagSymbol
+    "return the flag code which marks Symbol-like instances.
+     You have to check this single bit in the flag value when
+     checking for symbols."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(SYMBOL_INSTS) );
+%}
+!
+
+flagWeakPointers
+    "return the flag code for weak pointer indexed instances (i.e. WeakArray).
+     You have to mask the flag value with indexMask when comparing
+     it with flagWeakPointers."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(WKPOINTERARRAY) );
+%}
+!
+
+flagWords
+    "return the flag code for word-valued indexed instances (i.e. 2-byte).
+     You have to mask the flag value with indexMask when comparing
+     it with flagWords."
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(WORDARRAY) );
+%}
+    "
+     Behavior flagWords    
+    "
+!
+
+maskIndexType
+    "return a mask to extract all index-type bits"
+
+%{  /* NOCONTEXT */
+    /* this is defined as a primitive to get defines from stc.h */
+
+    RETURN ( _MKSMALLINT(ARRAYMASK) );
+%}
+! !
+
+!VMBehavior class methodsFor:'private'!
+
+basicNew
+    "I dont know how to do this ..."
+
+    ^ self subclassResponsibility
+!
+
+basicNew:size
+    "I dont know how to do this ..."
+
+    ^ self subclassResponsibility
+!
+
+new
+    "I dont know how to do this ..."
+
+    ^ self subclassResponsibility
+!
+
+new:size
+    "I dont know how to do this ..."
+
+    ^ self subclassResponsibility
+! !
+
+!VMBehavior class methodsFor:'queries'!
+
+isBuiltInClass
+    "this class is known by the run-time-system"
+
+    ^ true
+! !
+
+!VMBehavior methodsFor:'accessing'!
+
+flags
+    "return the receivers flag bits"
+
+    ^ flags
+!
+
+methodArray
+    "return the receivers method array.
+     Notice: this is not compatible with ST-80."
+
+    ^ methodArray
+!
+
+selectorArray 
+    "return the receivers selector array.
+     Notice: this is not compatible with ST-80."
+
+    ^ selectorArray
+!
+
+selectors:newSelectors methods:newMethods
+    "set both selector array and method array of the receiver,
+     and flush caches"
+
+    ObjectMemory flushCaches.
+    selectorArray := newSelectors.
+    methodArray := newMethods
+!
+
+superclass
+    "return the receivers superclass"
+
+    ^ superclass
+! !
+
+!VMBehavior methodsFor:'private accessing'!
+
+setFlags:aNumber
+    "set the flags.
+     Do NOT use it."
+
+    flags := aNumber
+!
+
+setMethodArray:anArray
+    "set the method array of the receiver.
+     this method is for special uses only - there will be no recompilation
+     and no change record written here.
+     NOT for general use."
+
+    methodArray := anArray
+!
+
+setSelectorArray:anArray
+    "set the selector array of the receiver.
+     this method is for special uses only - there will be no recompilation
+     and no change record written here.
+     NOT for general use."
+
+    selectorArray := anArray
+!
+
+setSelectors:sels methods:m
+    "set some inst vars. 
+     this method is for special uses only - there will be no recompilation
+     and no change record written here; 
+     Do NOT use it."
+
+    selectorArray := sels.
+    methodArray := m.
+!
+
+setSuperclass:aClass
+    "set the superclass of the receiver.
+     this method is for special uses only - there will be no recompilation
+     and no change record written here. Also, if the receiver class has
+     already been in use, future operation of the system is not guaranteed to
+     be correct, since no caches are flushed.
+     Therefore: do NOT use it; use Behavior>>superclass: (or flush the caches, at least)"
+
+    superclass := aClass
+! !
+
+!VMBehavior methodsFor:'queries'!
+
+cachedLookupMethodFor:aSelector
+    "return the method, which would be executed if aSelector was sent to
+     an instance of the receiver. I.e. the selector arrays of the receiver
+     and all of its superclasses are searched for aSelector.
+     Return the method, or nil if instances do not understand aSelector.
+     This interface provides exactly the same information as #lookupMethodFor:,
+     but uses the lookup-cache in the VM for faster search. 
+     However, keep in mind, that doing a lookup through the cache also adds new
+     entries and can thus slow down the system by polluting the cache with 
+     irrelevant entries. (do NOT loop over all objects calling this method).
+     Does NOT (currently) handle MI"
+
+%{  /* NOCONTEXT */
+    RETURN ( __lookup(self, aSelector, SENDER) );
+%}
+
+    "
+     String cachedLookupMethodFor:#=
+     String cachedLookupMethodFor:#asOrderedCollection
+    "
+!
+
+isBits
+    "return true, if instances have indexed byte or short instance variables.
+     Ignore long, float and double arrays, since ST-80 code using isBits are probably
+     not prepared to handle them correctly."
+
+%{  /* NOCONTEXT */
+
+    REGISTER int flags;
+
+    RETURN ( (((flags = (_intVal(_INST(flags)) & ARRAYMASK)) == BYTEARRAY)
+	     || (flags == WORDARRAY)) ? true : false ); 
+%}
+!
+
+isBytes
+    "return true, if instances have indexed byte instance variables"
+
+    "this could be defined as:
+	^ (flags bitAnd:(VMBehavior maskIndexType)) == VMBehavior flagBytes
+    "
+%{  /* NOCONTEXT */
+
+    RETURN ( ((_intVal(_INST(flags)) & ARRAYMASK) == BYTEARRAY) ? true : false ); 
+%}
+!
+
+isDoubles
+    "return true, if instances have indexed double instance variables"
+
+    "this could be defined as:
+	^ (flags bitAnd:(VMBehavior maskIndexType)) == VMBehavior flagDoubles
+    "
+%{  /* NOCONTEXT */
+
+    RETURN ( ((_intVal(_INST(flags)) & ARRAYMASK) == DOUBLEARRAY) ? true : false ); 
+%}
+!
+
+isFixed
+    "return true, if instances do not have indexed instance variables"
+
+    "this could be defined as:
+	^ self isVariable not
+    "
+
+%{  /* NOCONTEXT */
+
+    RETURN ( (_intVal(_INST(flags)) & ARRAYMASK) ? false : true ); 
+%}
+!
+
+isFloats
+    "return true, if instances have indexed float instance variables"
+
+    "this could be defined as:
+	^ (flags bitAnd:(VMBehavior maskIndexType)) == VMBehavior flagFloats
+    "
+%{  /* NOCONTEXT */
+
+    RETURN ( ((_intVal(_INST(flags)) & ARRAYMASK) == FLOATARRAY) ? true : false ); 
+%}
+!
+
+isLongs
+    "return true, if instances have indexed long instance variables"
+
+    "this could be defined as:
+	^ (flags bitAnd:(VMBehavior maskIndexType)) == VMBehavior flagLongs
+    "
+%{  /* NOCONTEXT */
+
+    RETURN ( ((_intVal(_INST(flags)) & ARRAYMASK) == LONGARRAY) ? true : false ); 
+%}
+!
+
+isPointers
+    "return true, if instances have pointer instance variables 
+     i.e. are either non-indexed or have indexed pointer variables"
+
+    "QUESTION: should we ignore WeakPointers ?"
+
+%{  /* NOCONTEXT */
+
+    REGISTER int flags;
+
+    flags = _intVal(_INST(flags)) & ARRAYMASK;
+    switch (flags) {
+	default:
+	    /* normal objects */
+	    RETURN ( true );
+
+	case BYTEARRAY:
+	case WORDARRAY:
+	case LONGARRAY:
+	case FLOATARRAY:
+	case DOUBLEARRAY:
+	    RETURN (false );
+
+	case WKPOINTERARRAY:
+	    /* what about those ? */
+	    RETURN (true );
+    }
+%}
+!
+
+isVariable
+    "return true, if instances have indexed instance variables"
+
+    "this could be defined as:
+	^ (flags bitAnd:(VMBehavior maskIndexType)) ~~ 0
+     "
+
+%{  /* NOCONTEXT */
+
+    RETURN ( (_intVal(_INST(flags)) & ARRAYMASK) ? true : false ); 
+%}
+!
+
+isWords
+    "return true, if instances have indexed short instance variables"
+
+    "this could be defined as:
+	^ (flags bitAnd:(VMBehavior maskIndexType)) == VMBehavior flagWords
+    "
+%{  /* NOCONTEXT */
+
+    RETURN ( ((_intVal(_INST(flags)) & ARRAYMASK) == WORDARRAY) ? true : false ); 
+%}
+!
+
+lookupMethodFor:aSelector
+    "return the method, which would be executed if aSelector was sent to
+     an instance of the receiver. I.e. the selector arrays of the receiver
+     and all of its superclasses are searched for aSelector.
+     Return the method, or nil if instances do not understand aSelector.
+     EXPERIMENTAL: take care of multiple superclasses."
+
+    |m cls|
+
+    cls := self.
+    [cls notNil] whileTrue:[
+	m := cls compiledMethodAt:aSelector.
+	m notNil ifTrue:[^ m].
+	cls := cls superclass
+    ].
+    ^ nil
+! !
+
+!VMBehavior class methodsFor:'documentation'!
+
+version
+    ^ '$Header: /cvs/stx/stx/libbasic/not_delivered/VMBehavior.st,v 1.1 1996/09/12 01:03:24 cg Exp $'
+! !
+VMBehavior initialize!
+
+
+
+
+
--- a/resources/af.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/af.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/af.rs,v 1.3 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/af.rs,v 1.3 2004/03/15 16:39:09 cg Exp $
 ;
 ; Afrikaans strings
 ;
@@ -48,3 +48,10 @@
 'oct'         'okt'
 'nov'         'nov'
 'dec'         'des'
+
+
+
+
+
+
+
--- a/resources/el.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/el.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-7
 
-; $Header: /cvs/stx/stx/libbasic/resources/el.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/el.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; Greek strings
 ;
@@ -48,3 +48,10 @@
 'oct'         'ïêô'
 'nov'         'íïÝ'
 'dec'         'äåê'
+
+
+
+
+
+
+
--- a/resources/en.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/en.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/en.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/en.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; English date strings
 ;
@@ -143,3 +143,10 @@
 #endif
 
 MAY_ABBREV                      ? 'may'
+
+
+
+
+
+
+
--- a/resources/eo.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/eo.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding utf8
 
-; $Header: /cvs/stx/stx/libbasic/resources/eo.rs,v 1.3 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/eo.rs,v 1.3 2004/03/15 16:39:09 cg Exp $
 ;
 ; Esperanto strings
 ;
@@ -48,3 +48,10 @@
 'oct'         'okt'
 ; 'nov'         'nov'
 ; 'dec'         'dec'
+
+
+
+
+
+
+
--- a/resources/fr.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/fr.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/fr.rs,v 1.3 2008-02-05 12:23:42 sr Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/fr.rs,v 1.3 2008/02/05 12:23:42 sr Exp $
 ;
 ; French strings
 ;
@@ -50,3 +50,10 @@
 'oct'           'oct'
 'nov'           'nov'
 'dec'           'déc'
+
+
+
+
+
+
+
--- a/resources/hu.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/hu.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding utf-8
 
-; $Header: /cvs/stx/stx/libbasic/resources/hu.rs,v 1.2 2006-10-23 10:20:55 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/hu.rs,v 1.2 2006/10/23 10:20:55 cg Exp $
 ;
 ; Hungarian strings
 ;
@@ -48,3 +48,10 @@
 'oct'           'okt'
 'nov'           'nov'
 'dec'           'dec'
+
+
+
+
+
+
+
--- a/resources/it.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/it.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/it.rs,v 1.4 2006-10-28 14:11:17 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/it.rs,v 1.4 2006/10/28 14:11:17 cg Exp $
 ;
 ; Italian strings
 ;
@@ -54,3 +54,10 @@
 'oct'           'ott'
 'nov'           'nov'
 'dec'           'dic'
+
+
+
+
+
+
+
--- a/resources/ja.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/ja.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding utf-8
 
-; $Header: /cvs/stx/stx/libbasic/resources/ja.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/ja.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; Japanese strings
 ;
@@ -59,3 +59,10 @@
 'fri'         '金曜'
 'sat'         '土曜'
 'sun'         '日曜'
+
+
+
+
+
+
+
--- a/resources/nl.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/nl.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/nl.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/nl.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; Dutch strings
 ;
@@ -48,3 +48,10 @@
 'oct'           'okt'
 'nov'           'nov'
 'dec'           'dec'
+
+
+
+
+
+
+
--- a/resources/no.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/no.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/no.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/no.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; Norwegian strings
 ;
@@ -48,3 +48,10 @@
 'oct'         'okt'
 'nov'         'nov'
 'dec'         'des'
+
+
+
+
+
+
+
--- a/resources/pt.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/pt.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/pt.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/pt.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; Portuguese strings
 ;
@@ -49,3 +49,10 @@
 'oct'         'out'
 'nov'         'nov'
 'dec'         'dez'
+
+
+
+
+
+
+
--- a/resources/resources.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/resources.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,7 +1,7 @@
 #encoding ascii
 
 ;
-; $Header: /cvs/stx/stx/libbasic/resources/resources.rs,v 1.8 2008-11-28 16:44:55 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/resources.rs,v 1.8 2008/11/28 16:44:55 cg Exp $
 ;
 
 #if Language == #af
@@ -128,3 +128,10 @@
 #else
 'TIME_FORMAT'                       ? 24
 #endif
+
+
+
+
+
+
+
--- a/resources/ro.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/ro.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-2
 
-; $Header: /cvs/stx/stx/libbasic/resources/ro.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/ro.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; Romanian strings
 ;
@@ -48,3 +48,10 @@
 'oct'         'oct'
 'nov'         'noi'
 'dec'         'dec'
+
+
+
+
+
+
+
--- a/resources/ru.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/ru.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-5
 
-; $Header: /cvs/stx/stx/libbasic/resources/ru.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/ru.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; Russian strings
 ;
@@ -48,3 +48,10 @@
 'oct'         'ÞÚâ'       "/ ???
 'nov'         'ÝÞï'       "/ ???
 'dec'         'ÔÕÚ'       "/ ???
+
+
+
+
+
+
+
--- a/resources/sv.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/sv.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/sv.rs,v 1.3 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/sv.rs,v 1.3 2004/03/15 16:39:09 cg Exp $
 ;
 ; Swedish strings
 ;
@@ -52,3 +52,10 @@
 'oct'           'okt'
 'nov'           'nov'
 'dec'           'dec'
+
+
+
+
+
+
+
--- a/resources/tr.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/tr.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding iso8859-1
 
-; $Header: /cvs/stx/stx/libbasic/resources/tr.rs,v 1.2 2004-03-15 16:39:09 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/tr.rs,v 1.2 2004/03/15 16:39:09 cg Exp $
 ;
 ; Turkish strings
 ;
@@ -48,3 +48,10 @@
 'oct'         'eki'
 'nov'         'kas'
 'dec'         'ara'
+
+
+
+
+
+
+
--- a/resources/zh.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/zh.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding utf8
 
-; $Header: /cvs/stx/stx/libbasic/resources/zh.rs,v 1.2 2008-11-28 16:44:28 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/zh.rs,v 1.2 2008/11/28 16:44:28 cg Exp $
 ;
 ; Chinese simplified
 ; extracted from google by claus - can someone proofread, please.
@@ -48,3 +48,10 @@
 'oct'         'å月'
 'nov'         'å一月'
 'dec'         'å二月'
+
+
+
+
+
+
+
--- a/resources/zh_trad.rs	Wed Mar 27 20:36:15 2013 +0100
+++ b/resources/zh_trad.rs	Thu Mar 28 12:21:50 2013 +0000
@@ -1,6 +1,6 @@
 #encoding utf8
 
-; $Header: /cvs/stx/stx/libbasic/resources/zh_trad.rs,v 1.2 2008-11-28 16:50:03 cg Exp $
+; $Header: /cvs/stx/stx/libbasic/resources/zh_trad.rs,v 1.2 2008/11/28 16:50:03 cg Exp $
 ;
 ; Chinese traditional
 ; this file contains 8bit national characters;
@@ -9,3 +9,10 @@
 #include 'zh.rs'
 
 ; please redefine any differences to traditional chinese below
+
+
+
+
+
+
+
--- a/stx_libbasic.st	Wed Mar 27 20:36:15 2013 +0100
+++ b/stx_libbasic.st	Thu Mar 28 12:21:50 2013 +0000
@@ -11,7 +11,7 @@
 "
 "{ Package: 'stx:libbasic' }"
 
-LibraryDefinition subclass:#stx_libbasic
+LibraryDefinition subclass:#'stx_libbasic'
 	instanceVariableNames:''
 	classVariableNames:''
 	poolDictionaries:''
@@ -41,6 +41,7 @@
 "
 ! !
 
+
 !stx_libbasic class methodsFor:'description'!
 
 excludedFromPreRequisites
@@ -48,25 +49,25 @@
      preRequisites scan. See #preRequisites for more."
 
     ^ #(
-        #'exept:ctypes'    "CType - referenced by ExternalLibraryFunction>>ffiTypeSymbolForType: "
-        #'exept:expecco'    "Expecco::ExpeccoXMLDecoder - referenced by ClassDescription>>iconInBrowserForVariableNamed: "
-        #'exept:libcrypt'    "HashRandom - referenced by HashStream class>>random "
-        #'stx:goodies'    "LockedFileStream - referenced by ClassDescription>>changesStream "
-        #'stx:goodies/simpleServices'    "STXScriptingServer - referenced by StandaloneStartup class>>handleScriptingOptionsFromArguments: "
-        #'stx:goodies/sunit'    "TestRunner - referenced by UserPreferences>>testRunnerClass "
-        #'stx:goodies/xml/stx'    "XMLCoder - referenced by ClassDescription>>fileOutXMLString:on: "
-        #'stx:goodies/xml/vw'    "XML::XMLParser - referenced by PeekableStream>>fileInXMLNotifying:passChunk: "
-        #'stx:libbasic2'    "List - referenced by Collection>>asList "
-        #'stx:libbasic3'    "ClassOrganizer - referenced by ClassDescription>>organization "
-        #'stx:libboss'    "BinaryObjectStorage - referenced by PeekableStream>>fileInBinary "
-        #'stx:libcomp'    "Parser - referenced by CharacterArray>>isValidSmalltalkIdentifier "
-        #'stx:libcompat'    "Dolphin::ClassCategoriesReader - referenced by ClassDescription>>categoriesForClass "
-        #'stx:libhtml'    "URL - referenced by CharacterArray>>asURL "
-        #'stx:libtool'    "Tools::ToDoListBrowser - referenced by ClassBuilder>>checkInstvarRedefsWith:subclassOf:old:name: "
-        #'stx:libview'    "Image - referenced by UserPreferences class>>saveSettings:in: "
-        #'stx:libview2'    "ApplicationModel - referenced by ApplicationDefinition class>>startupClassName_code "
-        #'stx:libwidg'    "Button - referenced by UserPreferences class>>saveSettings:in: "
-        #'stx:libwidg2'    "ProgressNotification - referenced by UserNotification class>>notify:progress: "
+	#'exept:ctypes'    "CType - referenced by ExternalLibraryFunction>>ffiTypeSymbolForType: "
+	#'exept:expecco'    "Expecco::ExpeccoXMLDecoder - referenced by ClassDescription>>iconInBrowserForVariableNamed: "
+	#'exept:libcrypt'    "HashRandom - referenced by HashStream class>>random "
+	#'stx:goodies'    "LockedFileStream - referenced by ClassDescription>>changesStream "
+	#'stx:goodies/simpleServices'    "STXScriptingServer - referenced by StandaloneStartup class>>handleScriptingOptionsFromArguments: "
+	#'stx:goodies/sunit'    "TestRunner - referenced by UserPreferences>>testRunnerClass "
+	#'stx:goodies/xml/stx'    "XMLCoder - referenced by ClassDescription>>fileOutXMLString:on: "
+	#'stx:goodies/xml/vw'    "XML::XMLParser - referenced by PeekableStream>>fileInXMLNotifying:passChunk: "
+	#'stx:libbasic2'    "List - referenced by Collection>>asList "
+	#'stx:libbasic3'    "ClassOrganizer - referenced by ClassDescription>>organization "
+	#'stx:libboss'    "BinaryObjectStorage - referenced by PeekableStream>>fileInBinary "
+	#'stx:libcomp'    "Parser - referenced by CharacterArray>>isValidSmalltalkIdentifier "
+	#'stx:libcompat'    "Dolphin::ClassCategoriesReader - referenced by ClassDescription>>categoriesForClass "
+	#'stx:libhtml'    "URL - referenced by CharacterArray>>asURL "
+	#'stx:libtool'    "Tools::ToDoListBrowser - referenced by ClassBuilder>>checkInstvarRedefsWith:subclassOf:old:name: "
+	#'stx:libview'    "Image - referenced by UserPreferences class>>saveSettings:in: "
+	#'stx:libview2'    "ApplicationModel - referenced by ApplicationDefinition class>>startupClassName_code "
+	#'stx:libwidg'    "Button - referenced by UserPreferences class>>saveSettings:in: "
+	#'stx:libwidg2'    "ProgressNotification - referenced by UserNotification class>>notify:progress: "
     )
 !
 
@@ -84,6 +85,8 @@
     )
 !
 
+
+
 referencedPreRequisites
     "list all packages containing classes referenced by the packages's members.
      This list can be maintained manually or (better) generated and
@@ -96,6 +99,7 @@
     )
 ! !
 
+
 !stx_libbasic class methodsFor:'description - compilation'!
 
 additionalBaseAddressDefinition_bc_dot_mak
@@ -120,6 +124,7 @@
     "Created: / 23-08-2006 / 11:06:17 / cg"
 ! !
 
+
 !stx_libbasic class methodsFor:'description - contents'!
 
 classNamesAndAttributes
@@ -129,399 +134,400 @@
      Attributes are: #autoload or #<os> where os is one of win32, unix,..."
 
     ^ #(
-        "<className> or (<className> attributes...) in load order"
-        Autoload
-        Object
-        ProtoObject
-        (AbstractDesktop autoload)
-        AbstractOperatingSystem
-        AbstractSourceFileReader
-        Annotation
-        (BadRomanNumberFormatError autoload)
-        Behavior
-        Boolean
-        CharacterEncoder
-        (#'CharacterEncoderImplementations::BIG5' autoload)
-        (#'CharacterEncoderImplementations::CNS11643' autoload)
-        (#'CharacterEncoderImplementations::GB2313_1980' autoload)
-        (#'CharacterEncoderImplementations::HANGUL' autoload)
-        (#'CharacterEncoderImplementations::ISO10646_to_JavaText' autoload)
-        (#'CharacterEncoderImplementations::ISO10646_to_SGML' autoload)
-        (#'CharacterEncoderImplementations::JIS0201' autoload)
-        (#'CharacterEncoderImplementations::JIS0208' autoload)
-        (#'CharacterEncoderImplementations::JIS0208_to_EUC' autoload)
-        (#'CharacterEncoderImplementations::JIS0208_to_JIS7' autoload)
-        (#'CharacterEncoderImplementations::JIS0208_to_SJIS' autoload)
-        (#'CharacterEncoderImplementations::JIS0212' autoload)
-        (#'CharacterEncoderImplementations::JOHAB' autoload)
-        (#'CharacterEncoderImplementations::KOI7' autoload)
-        (#'CharacterEncoderImplementations::KSC5601' autoload)
-        (#'CharacterEncoderImplementations::MAC_Arabic' autoload)
-        (#'CharacterEncoderImplementations::MAC_CentralEuropean' autoload)
-        (#'CharacterEncoderImplementations::MAC_Croatian' autoload)
-        (#'CharacterEncoderImplementations::MAC_Cyrillic' autoload)
-        (#'CharacterEncoderImplementations::MAC_Dingbats' autoload)
-        (#'CharacterEncoderImplementations::MAC_Farsi' autoload)
-        (#'CharacterEncoderImplementations::MAC_Greek' autoload)
-        (#'CharacterEncoderImplementations::MAC_Hebrew' autoload)
-        (#'CharacterEncoderImplementations::MAC_Iceland' autoload)
-        (#'CharacterEncoderImplementations::MAC_Japanese' autoload)
-        (#'CharacterEncoderImplementations::MAC_Korean' autoload)
-        (#'CharacterEncoderImplementations::MAC_Roman' autoload)
-        (#'CharacterEncoderImplementations::MAC_Romanian' autoload)
-        (#'CharacterEncoderImplementations::MAC_Symbol' autoload)
-        (#'CharacterEncoderImplementations::MAC_Thai' autoload)
-        (#'CharacterEncoderImplementations::MAC_Turkish' autoload)
-        (#'CharacterEncoderImplementations::NEXT' autoload)
-        ClassBuilder
-        ClassCategoryReader
-        (CmdLineOption autoload)
-        (CmdLineOptionError autoload)
-        (CmdLineParser autoload)
-        (CmdLineParserTest autoload)
-        Collection
-        ConfigurableFeatures
-        Context
-        Continuation
-        Delay
-        ExecutableFunction
-        ExternalAddress
-        ExternalLibrary
-        Filename
-        (GNOMEDesktop autoload)
-        GenericException
-        Geometric
-        (ImaginaryResultError autoload)
-        InlineObject
-        InterestConverter
-        (LargeFloat autoload)
-        Link
-        Lookup
-        (MacFilename macos autoload)
-        Magnitude
-        (MappedExternalBytes autoload)
-        Message
-        MiniDebugger
-        MiniInspector
-        MiniLogger
-        (NaiveRomanNumberFormatNotification autoload)
-        NameSpace
-        (NotANumber autoload)
-        (NumberConversionError autoload)
-        (NumberFormatError autoload)
-        OSErrorHolder
-        OSProcess
-        ObjectMemory
-        (OpenVMSFileHandle vms)
-        (OpenVMSFilename vms)
-        (OpenVMSOperatingSystem vms)
-        (PCFilename win32)
-        PackageId
-        ProcessorScheduler
-        ProgrammingLanguage
-        Project
-        ProjectDefinition
-        (QualifiedName autoload)
-        ReadEvalPrintLoop
-        RecursionLock
-        Registry
-        (RomanNumberFormatError autoload)
-        Semaphore
-        SharedPool
-        Signal
-        Smalltalk
-        (SmalltalkDesktop autoload)
-        StandaloneStartup
-        Stream
-        SystemChangeNotifier
-        (SystemNotification autoload)
-        (TextCollectorStream autoload)
-        (UnboundedExternalStream autoload)
-        UndefinedObject
-        (UnixDesktop autoload)
-        UserMessage
-        Visitor
-        (WeakValueIdentityDictionary autoload)
-        (Win32Constants win32)
-        (Win32FILEHandle win32)
-        (Win32Handle win32)
-        (Win32OperatingSystem win32)
-        (Win32Process win32)
-        (WindowsDesktop autoload)
-        (XDGDesktop autoload)
-        AbstractTime
-        ApplicationDefinition
-        ArithmeticValue
-        AspectVisitor
-        AutoDeletedFilename
-        Bag
-        BlockContext
-        BuiltinLookup
-        CachingRegistry
-        Character
-        #'CharacterEncoderImplementations::ISO10646_1'
-        #'CharacterEncoderImplementations::SingleByteEncoder'
-        #'CharacterEncoderImplementations::TwoByteEncoder'
-        CompiledCode
-        ControlInterrupt
-        Date
-        Exception
-        ExternalFunction
-        False
-        HandleRegistry
-        HashStream
-        InlineObjectPrototype
-        KeyedCollection
-        LibraryDefinition
-        LookupKey
-        MessageSend
-        NamespaceAwareLookup
-        NoHandlerError
-        Notification
-        OSHandle
-        PeekableStream
-        Process
-        QuerySignal
-        Rectangle
-        SequenceableCollection
-        Set
-        SmalltalkChunkFileSourceReader
-        SmalltalkLanguage
-        True
-        UnixFilename
-        WeakInterestConverter
-        ArrayedCollection
-        Association
-        Block
-        #'CharacterEncoderImplementations::ASCII'
-        #'CharacterEncoderImplementations::CP437'
-        #'CharacterEncoderImplementations::EBCDIC'
-        #'CharacterEncoderImplementations::ISO10646_to_UTF16BE'
-        #'CharacterEncoderImplementations::ISO10646_to_UTF8'
-        #'CharacterEncoderImplementations::ISO8859_1'
-        #'CharacterEncoderImplementations::ISO8859_10'
-        #'CharacterEncoderImplementations::ISO8859_11'
-        #'CharacterEncoderImplementations::ISO8859_13'
-        #'CharacterEncoderImplementations::ISO8859_14'
-        #'CharacterEncoderImplementations::ISO8859_15'
-        #'CharacterEncoderImplementations::ISO8859_16'
-        #'CharacterEncoderImplementations::ISO8859_2'
-        #'CharacterEncoderImplementations::ISO8859_3'
-        #'CharacterEncoderImplementations::ISO8859_4'
-        #'CharacterEncoderImplementations::ISO8859_5'
-        #'CharacterEncoderImplementations::ISO8859_6'
-        #'CharacterEncoderImplementations::ISO8859_7'
-        #'CharacterEncoderImplementations::ISO8859_8'
-        #'CharacterEncoderImplementations::KOI8_R'
-        #'CharacterEncoderImplementations::MS_Ansi'
-        #'CharacterEncoderImplementations::MS_Arabic'
-        #'CharacterEncoderImplementations::MS_Baltic'
-        #'CharacterEncoderImplementations::MS_Cyrillic'
-        #'CharacterEncoderImplementations::MS_EastEuropean'
-        #'CharacterEncoderImplementations::MS_Greek'
-        #'CharacterEncoderImplementations::MS_Hebrew'
-        #'CharacterEncoderImplementations::MS_Symbol'
-        #'CharacterEncoderImplementations::MS_Turkish'
-        ClassDescription
-        Complex
-        ControlRequest
-        Dictionary
-        EncodedStream
-        EndOfStreamNotification
-        Error
-        ExternalFunctionCallback
-        ExternalLibraryFunction
-        HaltInterrupt
-        IdentitySet
-        LinkedList
-        MD5Stream
-        Method
-        MethodDictionary
-        Number
-        OSFileHandle
-        ObjectCoder
-        OrderedCollection
-        Point
-        PositionableStream
-        Query
-        ReadOnlySequenceableCollection
-        RecursiveStoreError
-        SHA1Stream
-        Time
-        TimeoutNotification
-        Timestamp
-        UserInterrupt
-        UserNotification
-        YesToAllConfirmation
-        #'stx_libbasic'
-        AbortAllOperationRequest
-        AbortAllOperationWantedQuery
-        AbstractSourceFileWriter
-        ActivityNotification
-        Array
-        BreakPointInterrupt
-        #'CharacterEncoderImplementations::ISO10646_to_UTF16LE'
-        #'CharacterEncoderImplementations::ISO8859_9'
-        #'CharacterEncoderImplementations::KOI8_U'
-        CheapBlock
-        ClassBuildError
-        ElementBoundsError
-        FileDirectory
-        Fraction
-        GetOpt
-        IdentityDictionary
-        InlineObjectClassDescription
-        Integer
-        Interval
-        IsDebuggingQuery
-        LimitedPrecisionReal
-        MeasurementValue
-        MetaNumber
-        Metaclass
-        MethodWithBreakpoints
-        OsError
-        PluginSupport
-        ProceedableError
-        QueryWithoutDefault
-        ReadStream
-        RecursionError
-        RecursiveExceptionError
-        RestartProcessRequest
-        SameForAllNotification
-        SemaphoreSet
-        SignalSet
-        SnapshotError
-        SortedCollection
-        StringCollection
-        TerminateProcessRequest
-        UninterpretedBytes
-        (UnixFileDescriptorHandle unix)
-        (UnixFileHandle unix)
-        (UnixOperatingSystem unix)
-        UserConfirmation
-        UserInformation
-        UtcTimestamp
-        VMInternalError
-        VarArgBlock
-        Warning
-        WeakArray
-        WeakIdentitySet
-        WeakValueDictionary
-        WriteStream
-        AbortOperationRequest
-        AbstractNumberVector
-        AllocationFailure
-        AmbiguousMessage
-        ArithmeticError
-        AssertionFailedError
-        AutoloadMetaclass
-        ByteArray
-        CharacterArray
-        CharacterWriteStream
-        Class
-        ContextError
-        ConversionError
-        DeepCopyError
-        ExceptionHandlerSet
-        ExecutionError
-        ExternalBytes
-        FixedPoint
-        Float
-        ImmutableArray
-        Infinity
-        InvalidPatchError
-        LargeInteger
-        LongFloat
-        MessageNotUnderstood
-        NoModificationError
-        NotFoundError
-        OSSignalInterrupt
-        OsIllegalOperation
-        OsInaccessibleError
-        OsInvalidArgumentsError
-        OsNeedRetryError
-        OsNoResourcesError
-        OsNotification
-        OsTransferFaultError
-        PrivateMetaclass
-        ProceedError
-        ReadWriteStream
-        ShortFloat
-        SignalError
-        SmallInteger
-        SmalltalkChunkFileSourceWriter
-        SomeNumber
-        StreamError
-        SubclassResponsibilityError
-        TimeoutError
-        UnimplementedFunctionalityError
-        UserPreferences
-        VarArgCheapBlock
-        WeakIdentityDictionary
-        ArgumentError
-        CannotResumeError
-        CannotReturnError
-        CharacterEncoderError
-        DateConversionError
-        DomainError
-        DoubleArray
-        EndOfStreamError
-        ExternalStream
-        ExternalStructure
-        FloatArray
-        ImmutableByteArray
-        IncompleteNextCountError
-        IndexNotFoundError
-        InvalidCodeError
-        InvalidModeError
-        InvalidOperationError
-        KeyNotFoundError
-        MallocFailure
-        NonBooleanReceiverError
-        OpenError
-        PositionError
-        PositionOutOfBoundsError
-        PrimitiveFailure
-        RangeError
-        ReadError
-        StreamIOError
-        StreamNotOpenError
-        String
-        TimeConversionError
-        TwoByteString
-        UnorderedNumbersError
-        UnprotectedExternalBytes
-        WeakDependencyDictionary
-        WriteError
-        WrongProceedabilityError
-        BadLiteralsError
-        DecodingError
-        EncodingError
-        FileDoesNotExistException
-        FileStream
-        ImmutableString
-        InvalidByteCodeError
-        InvalidInstructionError
-        InvalidReadError
-        InvalidWriteError
-        NoByteCodeError
-        NonIntegerIndexError
-        NonPositionableExternalStream
-        OverflowError
-        SubscriptOutOfBoundsError
-        Symbol
-        UnderflowError
-        Unicode16String
-        WrongNumberOfArgumentsError
-        ZeroDivide
-        CharacterRangeError
-        DirectoryStream
-        InvalidEncodingError
-        PipeStream
-        MethodNotAppropriateError
-        AbstractClassInstantiationError
-        InvalidTypeError
-        (OSXOperatingSystem unix)
+	"<className> or (<className> attributes...) in load order"
+	Autoload
+	Object
+	ProtoObject
+	(AbstractDesktop autoload)
+	AbstractOperatingSystem
+	AbstractSourceFileReader
+	Annotation
+	(BadRomanNumberFormatError autoload)
+	Behavior
+	Boolean
+	CharacterEncoder
+	(#'CharacterEncoderImplementations::BIG5' autoload)
+	(#'CharacterEncoderImplementations::CNS11643' autoload)
+	(#'CharacterEncoderImplementations::GB2313_1980' autoload)
+	(#'CharacterEncoderImplementations::HANGUL' autoload)
+	(#'CharacterEncoderImplementations::ISO10646_to_JavaText' autoload)
+	(#'CharacterEncoderImplementations::ISO10646_to_SGML' autoload)
+	(#'CharacterEncoderImplementations::JIS0201' autoload)
+	(#'CharacterEncoderImplementations::JIS0208' autoload)
+	(#'CharacterEncoderImplementations::JIS0208_to_EUC' autoload)
+	(#'CharacterEncoderImplementations::JIS0208_to_JIS7' autoload)
+	(#'CharacterEncoderImplementations::JIS0208_to_SJIS' autoload)
+	(#'CharacterEncoderImplementations::JIS0212' autoload)
+	(#'CharacterEncoderImplementations::JOHAB' autoload)
+	(#'CharacterEncoderImplementations::KOI7' autoload)
+	(#'CharacterEncoderImplementations::KSC5601' autoload)
+	(#'CharacterEncoderImplementations::MAC_Arabic' autoload)
+	(#'CharacterEncoderImplementations::MAC_CentralEuropean' autoload)
+	(#'CharacterEncoderImplementations::MAC_Croatian' autoload)
+	(#'CharacterEncoderImplementations::MAC_Cyrillic' autoload)
+	(#'CharacterEncoderImplementations::MAC_Dingbats' autoload)
+	(#'CharacterEncoderImplementations::MAC_Farsi' autoload)
+	(#'CharacterEncoderImplementations::MAC_Greek' autoload)
+	(#'CharacterEncoderImplementations::MAC_Hebrew' autoload)
+	(#'CharacterEncoderImplementations::MAC_Iceland' autoload)
+	(#'CharacterEncoderImplementations::MAC_Japanese' autoload)
+	(#'CharacterEncoderImplementations::MAC_Korean' autoload)
+	(#'CharacterEncoderImplementations::MAC_Roman' autoload)
+	(#'CharacterEncoderImplementations::MAC_Romanian' autoload)
+	(#'CharacterEncoderImplementations::MAC_Symbol' autoload)
+	(#'CharacterEncoderImplementations::MAC_Thai' autoload)
+	(#'CharacterEncoderImplementations::MAC_Turkish' autoload)
+	(#'CharacterEncoderImplementations::NEXT' autoload)
+	ClassBuilder
+	ClassCategoryReader
+	(CmdLineOption autoload)
+	(CmdLineOptionError autoload)
+	(CmdLineParser autoload)
+	(CmdLineParserTest autoload)
+	Collection
+	ConfigurableFeatures
+	Context
+	Continuation
+	Delay
+	ExecutableFunction
+	ExternalAddress
+	ExternalLibrary
+	Filename
+	(GNOMEDesktop autoload)
+	GenericException
+	Geometric
+	(ImaginaryResultError autoload)
+	InlineObject
+	InterestConverter
+	(LargeFloat autoload)
+	Link
+	Lookup
+	(MacFilename macos autoload)
+	Magnitude
+	(MappedExternalBytes autoload)
+	Message
+	MiniDebugger
+	MiniInspector
+	MiniLogger
+	(NaiveRomanNumberFormatNotification autoload)
+	NameSpace
+	(NotANumber autoload)
+	(NumberConversionError autoload)
+	(NumberFormatError autoload)
+	OSErrorHolder
+	OSProcess
+	ObjectMemory
+	(OpenVMSFileHandle vms )
+	(OpenVMSFilename vms )
+	(OpenVMSOperatingSystem vms )
+	(PCFilename win32 )
+	PackageId
+	ProcessorScheduler
+	ProgrammingLanguage
+	Project
+	ProjectDefinition
+	(QualifiedName autoload)
+	ReadEvalPrintLoop
+	RecursionLock
+	Registry
+	(RomanNumberFormatError autoload)
+	Semaphore
+	SharedPool
+	Signal
+	Smalltalk
+	(SmalltalkDesktop autoload)
+	StandaloneStartup
+	Stream
+	SystemChangeNotifier
+	(SystemNotification autoload)
+	(TextCollectorStream autoload)
+	(UnboundedExternalStream autoload)
+	UndefinedObject
+	(UnixDesktop autoload)
+	UserMessage
+	Visitor
+	(WeakValueIdentityDictionary autoload)
+	(Win32Constants win32 )
+	(Win32FILEHandle win32 )
+	(Win32Handle win32 )
+	(Win32OperatingSystem win32 )
+	(Win32Process win32 )
+	(WindowsDesktop autoload)
+	(XDGDesktop autoload)
+	AbstractTime
+	ApplicationDefinition
+	ArithmeticValue
+	AspectVisitor
+	AutoDeletedFilename
+	Bag
+	BlockContext
+	BuiltinLookup
+	CachingRegistry
+	Character
+	#'CharacterEncoderImplementations::ISO10646_1'
+	#'CharacterEncoderImplementations::SingleByteEncoder'
+	#'CharacterEncoderImplementations::TwoByteEncoder'
+	CompiledCode
+	ControlInterrupt
+	Date
+	Exception
+	ExternalFunction
+	False
+	HandleRegistry
+	HashStream
+	InlineObjectPrototype
+	KeyedCollection
+	LibraryDefinition
+	LookupKey
+	MessageSend
+	NamespaceAwareLookup
+	NoHandlerError
+	Notification
+	OSHandle
+	PeekableStream
+	Process
+	QuerySignal
+	Rectangle
+	SequenceableCollection
+	Set
+	SmalltalkChunkFileSourceReader
+	SmalltalkLanguage
+	True
+	UnixFilename
+	WeakInterestConverter
+	ArrayedCollection
+	Association
+	Block
+	#'CharacterEncoderImplementations::ASCII'
+	#'CharacterEncoderImplementations::CP437'
+	#'CharacterEncoderImplementations::EBCDIC'
+	#'CharacterEncoderImplementations::ISO10646_to_UTF16BE'
+	#'CharacterEncoderImplementations::ISO10646_to_UTF8'
+	#'CharacterEncoderImplementations::ISO8859_1'
+	#'CharacterEncoderImplementations::ISO8859_10'
+	#'CharacterEncoderImplementations::ISO8859_11'
+	#'CharacterEncoderImplementations::ISO8859_13'
+	#'CharacterEncoderImplementations::ISO8859_14'
+	#'CharacterEncoderImplementations::ISO8859_15'
+	#'CharacterEncoderImplementations::ISO8859_16'
+	#'CharacterEncoderImplementations::ISO8859_2'
+	#'CharacterEncoderImplementations::ISO8859_3'
+	#'CharacterEncoderImplementations::ISO8859_4'
+	#'CharacterEncoderImplementations::ISO8859_5'
+	#'CharacterEncoderImplementations::ISO8859_6'
+	#'CharacterEncoderImplementations::ISO8859_7'
+	#'CharacterEncoderImplementations::ISO8859_8'
+	#'CharacterEncoderImplementations::KOI8_R'
+	#'CharacterEncoderImplementations::MS_Ansi'
+	#'CharacterEncoderImplementations::MS_Arabic'
+	#'CharacterEncoderImplementations::MS_Baltic'
+	#'CharacterEncoderImplementations::MS_Cyrillic'
+	#'CharacterEncoderImplementations::MS_EastEuropean'
+	#'CharacterEncoderImplementations::MS_Greek'
+	#'CharacterEncoderImplementations::MS_Hebrew'
+	#'CharacterEncoderImplementations::MS_Symbol'
+	#'CharacterEncoderImplementations::MS_Turkish'
+	ClassDescription
+	Complex
+	ControlRequest
+	Dictionary
+	EncodedStream
+	EndOfStreamNotification
+	Error
+	ExternalFunctionCallback
+	ExternalLibraryFunction
+	HaltInterrupt
+	IdentitySet
+	LinkedList
+	MD5Stream
+	Method
+	MethodDictionary
+	Number
+	OSFileHandle
+	ObjectCoder
+	OrderedCollection
+	Point
+	PositionableStream
+	Query
+	ReadOnlySequenceableCollection
+	RecursiveStoreError
+	SHA1Stream
+	Time
+	TimeoutNotification
+	Timestamp
+	UserInterrupt
+	UserNotification
+	YesToAllConfirmation
+	#'stx_libbasic'
+	AbortAllOperationRequest
+	AbortAllOperationWantedQuery
+	AbstractSourceFileWriter
+	ActivityNotification
+	Array
+	BreakPointInterrupt
+	#'CharacterEncoderImplementations::ISO10646_to_UTF16LE'
+	#'CharacterEncoderImplementations::ISO8859_9'
+	#'CharacterEncoderImplementations::KOI8_U'
+	CheapBlock
+	ClassBuildError
+	ElementBoundsError
+	FileDirectory
+	Fraction
+	GetOpt
+	IdentityDictionary
+	InlineObjectClassDescription
+	Integer
+	Interval
+	IsDebuggingQuery
+	LimitedPrecisionReal
+	MeasurementValue
+	MetaNumber
+	Metaclass
+	MethodWithBreakpoints
+	OsError
+	PluginSupport
+	ProceedableError
+	QueryWithoutDefault
+	ReadStream
+	RecursionError
+	RecursiveExceptionError
+	RestartProcessRequest
+	SameForAllNotification
+	SemaphoreSet
+	SignalSet
+	SnapshotError
+	SortedCollection
+	StringCollection
+	TerminateProcessRequest
+	UninterpretedBytes
+	(UnixFileDescriptorHandle unix)
+	(UnixFileHandle unix)
+	(UnixOperatingSystem unix)
+	UserConfirmation
+	UserInformation
+	UtcTimestamp
+	VMInternalError
+	VarArgBlock
+	Warning
+	WeakArray
+	WeakIdentitySet
+	WeakValueDictionary
+	WriteStream
+	AbortOperationRequest
+	AbstractNumberVector
+	AllocationFailure
+	AmbiguousMessage
+	ArithmeticError
+	AssertionFailedError
+	AutoloadMetaclass
+	ByteArray
+	CharacterArray
+	CharacterWriteStream
+	Class
+	ContextError
+	ConversionError
+	DeepCopyError
+	ExceptionHandlerSet
+	ExecutionError
+	ExternalBytes
+	FixedPoint
+	Float
+	ImmutableArray
+	Infinity
+	InvalidPatchError
+	LargeInteger
+	LongFloat
+	MessageNotUnderstood
+	NoModificationError
+	NotFoundError
+	OSSignalInterrupt
+	OsIllegalOperation
+	OsInaccessibleError
+	OsInvalidArgumentsError
+	OsNeedRetryError
+	OsNoResourcesError
+	OsNotification
+	OsTransferFaultError
+	PrivateMetaclass
+	ProceedError
+	ReadWriteStream
+	ShortFloat
+	SignalError
+	SmallInteger
+	SmalltalkChunkFileSourceWriter
+	SomeNumber
+	StreamError
+	SubclassResponsibilityError
+	TimeoutError
+	UnimplementedFunctionalityError
+	UserPreferences
+	VarArgCheapBlock
+	WeakIdentityDictionary
+	ArgumentError
+	CannotResumeError
+	CannotReturnError
+	CharacterEncoderError
+	DateConversionError
+	DomainError
+	DoubleArray
+	EndOfStreamError
+	ExternalStream
+	ExternalStructure
+	FloatArray
+	ImmutableByteArray
+	IncompleteNextCountError
+	IndexNotFoundError
+	InvalidCodeError
+	InvalidModeError
+	InvalidOperationError
+	KeyNotFoundError
+	MallocFailure
+	NonBooleanReceiverError
+	OpenError
+	PositionError
+	PositionOutOfBoundsError
+	PrimitiveFailure
+	RangeError
+	ReadError
+	StreamIOError
+	StreamNotOpenError
+	String
+	TimeConversionError
+	TwoByteString
+	UnorderedNumbersError
+	UnprotectedExternalBytes
+	WeakDependencyDictionary
+	WriteError
+	WrongProceedabilityError
+	BadLiteralsError
+	DecodingError
+	EncodingError
+	FileDoesNotExistException
+	FileStream
+	ImmutableString
+	InvalidByteCodeError
+	InvalidInstructionError
+	InvalidReadError
+	InvalidWriteError
+	NoByteCodeError
+	NonIntegerIndexError
+	NonPositionableExternalStream
+	OverflowError
+	SubscriptOutOfBoundsError
+	Symbol
+	UnderflowError
+	Unicode16String
+	WrongNumberOfArgumentsError
+	ZeroDivide
+	CharacterRangeError
+	DirectoryStream
+	InvalidEncodingError
+	PipeStream
+	MethodNotAppropriateError
+	AbstractClassInstantiationError
+	InvalidTypeError
+	(#'CharacterEncoderImplementations::ISO10646_to_XMLUTF8' autoload)
+	(OSXOperatingSystem unix)
     )
 !
 
@@ -533,6 +539,7 @@
     )
 ! !
 
+
 !stx_libbasic class methodsFor:'description - project information'!
 
 applicationIconFileName
@@ -568,6 +575,7 @@
     ^ 'Smalltalk/X'
 ! !
 
+
 !stx_libbasic class methodsFor:'description - svn'!
 
 svnRevisionNr
@@ -577,6 +585,7 @@
     ^ "$SVN-Revision:"'exported'"$"
 ! !
 
+
 !stx_libbasic class methodsFor:'documentation'!
 
 version
@@ -590,4 +599,3 @@
 version_SVN
     ^ '§ Id: stx_libbasic.st 10648 2011-06-23 15:55:10Z vranyj1  §'
 ! !
-
--- a/vcmake.bat	Wed Mar 27 20:36:15 2013 +0100
+++ b/vcmake.bat	Thu Mar 28 12:21:50 2013 +0000
@@ -9,6 +9,12 @@
     call vcsetup.bat
     popd
 )
-make.exe -N -f bc.mak -DUSEVC %*
+@SET DEFINES=
+@REM Kludge got Mercurial, cannot be implemented in Borland make
+@FOR /F "tokens=*" %%i in ('hg root') do SET HGROOT=%%i
+@IF "%HGROOT%" NEQ "" SET DEFINES=%DEFINES% "-DHGROOT=%HGROOT%"
+make.exe -N -f bc.mak -DUSEVC=1 %DEFINES% %*
 
 
+
+
--- a/vms.mak	Wed Mar 27 20:36:15 2013 +0100
+++ b/vms.mak	Thu Mar 28 12:21:50 2013 +0000
@@ -2,7 +2,7 @@
 # DO NOT EDIT 
 # automatically generated from Make.proto
 #
-# $Header: /cvs/stx/stx/libbasic/vms.mak,v 1.9 2001-10-31 15:02:19 cg Exp $
+# $Header: /cvs/stx/stx/libbasic/vms.mak,v 1.9 2001/10/31 15:02:19 cg Exp $
 #
 TOP=..
 LIBNAME=libbasic
@@ -296,3 +296,10 @@
 $(OUTDIR)WriteStream.$(O) WriteStream.$(H): WriteStream.st $(STCHDR)  ../include/PositionableStream.$(H)  ../include/PeekableStream.$(H)  ../include/Stream.$(H)  ../include/Object.$(H) 
 $(OUTDIR)WrongProceedabilityError.$(O) WrongProceedabilityError.$(H): WrongProceedabilityError.st $(STCHDR)  ../include/SignalError.$(H)  ../include/ProceedableError.$(H)  ../include/Error.$(H)  ../include/Exception.$(H)  ../include/GenericException.$(H)  ../include/Object.$(H) 
 # ENDMAKEDEPEND
+
+
+
+
+
+
+