Merged 52f3ca7a321f and 90d541e96217 (branch default - CVS HEAD) jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 27 Sep 2013 23:47:30 +0100
branchjv
changeset 18098 2bbfe6952a44
parent 18097 52f3ca7a321f (current diff)
parent 15772 90d541e96217 (diff)
child 18099 8195a332b211
Merged 52f3ca7a321f and 90d541e96217 (branch default - CVS HEAD)
AbstractOperatingSystem.st
Behavior.st
Integer.st
Method.st
Object.st
OrderedCollection.st
ProjectDefinition.st
SequenceableCollection.st
Smalltalk.st
UserPreferences.st
--- a/AbstractOperatingSystem.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/AbstractOperatingSystem.st	Fri Sep 27 23:47:30 2013 +0100
@@ -3537,7 +3537,7 @@
 getNetworkMACAddressesForIf:ifName
     "return the MAC adress for interface ifName"
 
-    self getNetworkMACAddresses at:ifName ifAbsent:nil
+    ^ self getNetworkMACAddresses at:ifName ifAbsent:nil
 
     "Modified: / 17-11-2004 / 01:43:35 / cg"
 !
@@ -5843,8 +5843,8 @@
 getDesktopDirectory
     "{ Pragma: +optSpace }"
 
-    "return the name of the users desktop directory.
-     The fallback here returns the users home directory."
+    "return the name of the user's desktop directory.
+     The fallback here returns the user's home directory."
 
     ^ self getHomeDirectory
 
@@ -7261,11 +7261,11 @@
 !AbstractOperatingSystem class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.242 2013-07-13 20:40:45 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.244 2013-09-25 18:42:33 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.242 2013-07-13 20:40:45 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/AbstractOperatingSystem.st,v 1.244 2013-09-25 18:42:33 cg Exp $'
 ! !
 
 
--- a/Behavior.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/Behavior.st	Fri Sep 27 23:47:30 2013 +0100
@@ -1517,6 +1517,15 @@
     "Created: 16.4.1996 / 16:27:16 / cg"
 ! !
 
+!Behavior methodsFor:'cleanup'!
+
+lowSpaceCleanup
+    "ignored here - redefined in some classes to
+     cleanup in low-memory situations"
+
+    ^ self
+! !
+
 !Behavior methodsFor:'compiler interface'!
 
 browserClass
@@ -5025,10 +5034,10 @@
 !Behavior class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.348 2013-09-03 21:49:56 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.349 2013-09-25 14:10:10 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.348 2013-09-03 21:49:56 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Behavior.st,v 1.349 2013-09-25 14:10:10 cg Exp $'
 ! !
 
--- a/Integer.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/Integer.st	Fri Sep 27 23:47:30 2013 +0100
@@ -758,8 +758,6 @@
     "Modified: / 15.11.1999 / 20:35:20 / cg"
 ! !
 
-
-
 !Integer class methodsFor:'class initialization'!
 
 initialize
@@ -820,7 +818,6 @@
     "
 ! !
 
-
 !Integer class methodsFor:'prime numbers'!
 
 flushPrimeCache
@@ -1143,7 +1140,6 @@
     ^ self == Integer
 ! !
 
-
 !Integer methodsFor:'Compatibility-Dolphin'!
 
 & aNumber
@@ -1207,7 +1203,7 @@
 
 printStringRadix:aRadix padTo:sz
     "return a printed representation of the receiver in a given radix,
-     padded with spaces (at the right) up to size.
+     padded with zeros (at the left) up to size.
      If the printString is longer than size,
      it is returned unchanged (i.e. not truncated).
      See also printStringRadix:size:fill:"
@@ -4315,7 +4311,6 @@
     "Created: / 09-01-2012 / 17:18:06 / cg"
 ! !
 
-
 !Integer methodsFor:'special modulu arithmetic'!
 
 add_32:anInteger
@@ -5002,11 +4997,11 @@
 !Integer class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.285 2013-07-30 10:56:51 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.286 2013-09-23 13:11:40 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.285 2013-07-30 10:56:51 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Integer.st,v 1.286 2013-09-23 13:11:40 cg Exp $'
 ! !
 
 
--- a/Method.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/Method.st	Fri Sep 27 23:47:30 2013 +0100
@@ -3346,6 +3346,7 @@
      with aSelectorSymbol as selector."
 
     (self referencesLiteral:aSelectorSymbol) ifTrue:[
+        ^ true.
         ^ self messagesSent includesIdentical:aSelectorSymbol
     ].
     ^ false
@@ -3359,6 +3360,7 @@
     |msgs|
 
     ((self referencesLiteral:selectorSymbol1) or:[self referencesLiteral:selectorSymbol2]) ifTrue:[
+        ^ true.
         msgs := self messagesSent.
         ^ (msgs includesIdentical:selectorSymbol1) or:[msgs includesIdentical:selectorSymbol2]
     ].
@@ -3374,6 +3376,7 @@
     |msgs|
 
     (aCollectionOfSelectorSymbols contains:[:sym | self referencesLiteral:sym]) ifTrue:[
+        ^ true.
         msgs := self messagesSent.
         ^ aCollectionOfSelectorSymbols contains:[:sym | msgs includesIdentical:sym]
     ].
@@ -3851,11 +3854,11 @@
 !Method class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.424 2013-08-30 22:24:50 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.425 2013-09-24 21:36:13 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.424 2013-08-30 22:24:50 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Method.st,v 1.425 2013-09-24 21:36:13 cg Exp $'
 !
 
 version_HG
--- a/OSXOperatingSystem.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/OSXOperatingSystem.st	Fri Sep 27 23:47:30 2013 +0100
@@ -20,13 +20,27 @@
     "Modified: / 5.6.1998 / 18:35:18 / cg"
 ! !
 
+!OSXOperatingSystem class methodsFor:'users & groups'!
+
+getDesktopDirectory
+    "{ Pragma: +optSpace }"
+
+    "return the name of the user's desktop directory."
+
+    ^ self getHomeDirectory,'/Desktop'
+
+    "
+     OperatingSystem getDesktopDirectory
+    "
+! !
+
 !OSXOperatingSystem class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OSXOperatingSystem.st,v 1.1 2013-03-04 12:34:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OSXOperatingSystem.st,v 1.2 2013-09-25 18:41:05 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/OSXOperatingSystem.st,v 1.1 2013-03-04 12:34:14 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OSXOperatingSystem.st,v 1.2 2013-09-25 18:41:05 cg Exp $'
 ! !
 
--- a/Object.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/Object.st	Fri Sep 27 23:47:30 2013 +0100
@@ -1959,15 +1959,6 @@
     ^ aBlock ensure:[ self addDependent:someone ]
 ! !
 
-!Object methodsFor:'cleanup'!
-
-lowSpaceCleanup
-    "ignored here - redefined in some classes to
-     cleanup in low-memory situations"
-
-    ^ self
-! !
-
 !Object methodsFor:'comparing'!
 
 = anObject
@@ -8613,11 +8604,11 @@
 ?? defaultValue
      "a syntactic sugar-piece:
       much like ?, but sends #value to the argument if required.
-      (i.e. its the same as #ifNil:)
+      (i.e. it's the same as #ifNil:)
       If the receiver is nil, return the defaultValues value;
       otherwise, return the receiver.
       This method is only redefined in UndefinedObject - therefore,
-      the recevier is retuned here.
+      the receiver is retuned here.
 
       Thus, if foo and bar are simple variables or constants,
           foo ?? bar
@@ -9862,11 +9853,11 @@
 !Object class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.736 2013-08-29 10:33:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.738 2013-09-25 14:10:43 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.736 2013-08-29 10:33:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Object.st,v 1.738 2013-09-25 14:10:43 cg Exp $'
 !
 
 version_HG
--- a/OrderedCollection.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/OrderedCollection.st	Fri Sep 27 23:47:30 2013 +0100
@@ -1387,11 +1387,27 @@
     ^ super replaceFrom:start to:stop with:aCollection startingAt:repStart
 
     "
+     |c1 c2|
+
+     c1 := #(1 2 3 4 5 6) asOrderedCollection.
+     c2 := #(a b c d e f) asOrderedCollection.
+     c2 replaceFrom:3 to:6 with:c1.
+     c2        
+    "
+    "
+     |c1 c2|
+
+     c1 := #(1 2 3 4 5 6) asOrderedCollection.
+     c2 := #(a b c d e f) asOrderedCollection.
+     c2 replaceFrom:3 to:6 with:c1 startingAt:2.
+     c2   
+    "
+    "
      |c|
 
      c := #(1 2 3 4 5 6) asOrderedCollection.
      c replaceFrom:3 to:6 with:c startingAt:2.
-     c  
+     c    
     "
     "
      |c|
@@ -2018,6 +2034,6 @@
 !OrderedCollection class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OrderedCollection.st,v 1.109 2013-09-05 11:04:54 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OrderedCollection.st,v 1.110 2013-09-14 01:25:37 cg Exp $'
 ! !
 
--- a/OrderedDictionary.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/OrderedDictionary.st	Fri Sep 27 23:47:30 2013 +0100
@@ -171,7 +171,7 @@
 
 at: key put: anObject 
     "Set the value at key to be anObject. 
-     If key is not found, create a new entry for key and set is value to anObject. 
+     If key is not found, create a new entry for key and set its value to anObject. 
      If key is already present, the order remains unchanged.
      Return anObject."
 
@@ -334,8 +334,7 @@
     | key |
 
     key := anAssociation key.
-    (super includesKey: key)
-            ifFalse: [order add: key].
+    (super includesKey: key) ifFalse: [order add: key].
     ^ super add: anAssociation
 !
 
@@ -544,6 +543,21 @@
     ^ order collect:[:key | (aBlock value: (self at:key))].
 !
 
+detect: aBlock ifNone:exceptionBlock
+    "evaluate the argument, aBlock for each element in the receiver until
+     the block returns true; in this case return the element which caused
+     the true evaluation.
+     If none of the evaluations returns true, return the result of the
+     evaluation of the exceptionBlock"
+
+    order do:[:key | 
+        |el|
+
+        (aBlock value: (el := self at:key)) ifTrue:[^ el]
+    ].
+    ^ exceptionBlock value
+!
+
 do: aBlock 
     "Evaluate aBlock for each of the dictionary's values."
 
@@ -609,6 +623,21 @@
     ].
 !
 
+keysAndValuesDetect: aBlock ifNone:exceptionBlock
+    "evaluate the argument, aBlock for each element in the receiver until
+     the block returns true; in this case return the element which caused
+     the true evaluation.
+     If none of the evaluations returns true, return the result of the
+     evaluation of the exceptionBlock"
+
+    order do:[:key | 
+        |el|
+
+        (aBlock value:key value: (el := self at:key)) ifTrue:[^ el]
+    ].
+    ^ exceptionBlock value
+!
+
 keysAndValuesDo:aBlock
     "perform the block for all keys and values in the collection.
      Enumerate them in the order by which they were added.
@@ -987,10 +1016,10 @@
 !OrderedDictionary class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/OrderedDictionary.st,v 1.43 2013-08-21 11:16:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OrderedDictionary.st,v 1.44 2013-09-15 10:43:49 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/OrderedDictionary.st,v 1.43 2013-08-21 11:16:23 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/OrderedDictionary.st,v 1.44 2013-09-15 10:43:49 cg Exp $'
 ! !
 
--- a/ProjectDefinition.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/ProjectDefinition.st	Fri Sep 27 23:47:30 2013 +0100
@@ -714,11 +714,13 @@
     "
 !
 
-projectIsLoaded:something
-    projectIsLoaded := something.
-    something ifTrue:[
+projectIsLoaded:aBoolean
+    projectIsLoaded := aBoolean.
+    aBoolean ifTrue:[
         "register myself as dependent - I want to get notified on method changes"
         self class addDependent:self.
+        self postLoadAction.
+        self executeHooks: #postLoad.
     ].
 !
 
@@ -926,21 +928,18 @@
      This is used by the systembrowser to pass in a CodeGeneratorTool with undo support.
      If nil is passed in, the recurlar compiler is used (no undo support)"
 
-    |oldSpec newSpec newCode extensionMethods idx|
+    |oldSpec newSpec newCode idx|
 
     oldSpec := self extensionMethodNames.
-    newSpec := oldSpec copy.
-    extensionMethods := self extensionMethods.
-
-    idx := (1 to:newSpec size-1 by:2) 
+
+    idx := (1 to:oldSpec size-1 by:2) 
                 detect:[:i |
-                    ((newSpec at:i) = className)
-                    and:[ (newSpec at:i+1) = selector ]]
-                ifNone:nil.
-    idx isNil ifTrue:[ ^ self ].
+                    ((oldSpec at:i) = className)
+                    and:[ (oldSpec at:i+1) = selector ]]
+                ifNone:[ ^ self ].
 
     "/ attention: there are two spec-elements per method
-    newSpec := newSpec removeFromIndex:idx toIndex:idx+1.
+    newSpec := oldSpec copyWithoutIndex:idx toIndex:idx+1.
 
     newCode := self extensionMethodNames_code_For:newSpec.
     self compile:newCode categorized:'description - contents' using:compilerOrNil
@@ -1195,9 +1194,11 @@
 !
 
 initializeAllProjectDefinitions
-    "needs everything else (especially the compiler etc.) to be initialized.
-     Therefore, its not invoked by #initialize, but instead explicitely,
-     by Smalltalk"
+    "tells all already loaded project definition classes that it is loaded
+     (i.e. calls postLoadAction).
+     This needs everything else (especially the compiler etc.) to be initialized.
+     Therefore, it's not invoked by the projDef's #initialize, 
+     but instead explicitely, by Smalltalk as a late step in the startup."
 
     |isStandAloneApp|
 
@@ -5066,8 +5067,6 @@
 
         "/ mhmh - already done for dll-loaded packages
         "/ meOrMySecondIncarnation initializeAllClasses.
-        meOrMySecondIncarnation postLoadAction.
-        meOrMySecondIncarnation executeHooks: #postLoad.
 
         meOrMySecondIncarnation projectIsLoaded:true.
         meOrMySecondIncarnation ~~ self ifTrue:[
@@ -5914,9 +5913,9 @@
     "
 !
 
-executeHooks: hook
-    "Execute all hooks annotate by given symbol. Currently supported
-     hooks are: #preLoad, #postLoad, #preUnload."
+executeHooks: hookSymbol
+    "Execute all hooks annotated by the given hook-symbol. 
+     Currently supported hooks are: #preLoad, #postLoad, #preUnload."
 
     | cls |
 
@@ -5924,11 +5923,11 @@
 
     [ cls notNil ] whileTrue:[
         cls class selectorsAndMethodsDo:[:selector :method|
-            (method annotationAt: hook) notNil ifTrue:[
+            (method annotationAt: hookSymbol) notNil ifTrue:[
                 method numArgs == 0 ifTrue:[
                     self perform: selector
                 ] ifFalse:[
-                    self error:'Hook for %1 must have no arguments' mayProceed: true.
+                    self error:'Hook for %1 may not have arguments' mayProceed: true.
                 ]
             ]
         ].
@@ -7530,11 +7529,11 @@
 !ProjectDefinition class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/ProjectDefinition.st,v 1.482 2013-08-07 09:53:31 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ProjectDefinition.st,v 1.485 2013-09-23 08:20:42 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/ProjectDefinition.st,v 1.482 2013-08-07 09:53:31 stefan Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/ProjectDefinition.st,v 1.485 2013-09-23 08:20:42 stefan Exp $'
 !
 
 version_HG
--- a/SequenceableCollection.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/SequenceableCollection.st	Fri Sep 27 23:47:30 2013 +0100
@@ -380,6 +380,8 @@
     ^ self == SequenceableCollection
 ! !
 
+
+
 !SequenceableCollection methodsFor:'Compatibility-Squeak'!
 
 allButFirst
@@ -699,6 +701,7 @@
     ^ self replaceFrom:start to:stop with:anArray startingAt:repStart
 ! !
 
+
 !SequenceableCollection methodsFor:'accessing'!
 
 after:anObject
@@ -4235,6 +4238,24 @@
     "
 !
 
+copyWithoutIndex:firstIndex toIndex:lastIndex
+    "return a new collection consisting of receiver's elements
+     without the arguments elements stored from firstIndex to lastIndex"
+
+    |copy sz|
+
+    sz := self size - (lastIndex-firstIndex + 1).
+    copy := self copyEmptyAndGrow:sz.
+    copy replaceFrom:1 to:(firstIndex - 1) with:self startingAt:1.
+    copy replaceFrom:firstIndex to:sz with:self startingAt:(lastIndex + 1).
+    ^ copy
+
+    "
+     #(1 2 3 4 5 6 7 8 9 0) copyWithoutIndex:3 toIndex:5
+     'abcdefghijkl' copyWithoutIndex:5 toIndex:5
+    "
+!
+
 copyWithoutLast:count
     "return a new collection consisting of the receiver's elements
      except the last count elements.
@@ -7035,6 +7056,7 @@
     "Created: 14.2.1997 / 16:13:03 / cg"
 ! !
 
+
 !SequenceableCollection methodsFor:'searching'!
 
 detect:aBlock startingAt:startIndex
@@ -9185,11 +9207,11 @@
 !SequenceableCollection class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.351 2013-08-31 19:23:31 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.352 2013-09-23 08:20:18 stefan Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.351 2013-08-31 19:23:31 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/SequenceableCollection.st,v 1.352 2013-09-23 08:20:18 stefan Exp $'
 ! !
 
 
--- a/Smalltalk.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/Smalltalk.st	Fri Sep 27 23:47:30 2013 +0100
@@ -3363,7 +3363,7 @@
     "Modified: / 3.2.1998 / 14:22:46 / cg"
 !
 
-resolveName:nameIn inClass:aClass
+resolveName:aName inClass:aClass
     "resolve aName as if compiled within aClass;
      i.e. if it has a private class with this name, return it;
      if aName is known within the classes namespace, return that.
@@ -3371,30 +3371,30 @@
      This should be used whereever Smalltalk>>at: used to be used,
      to resolve a global by name."
 
-    |aName sym cls ns|
-
-    nameIn isNil ifTrue:[^ nil].
-    nameIn isBehavior ifTrue:[^ nameIn].       "/ already resolved
-    aName := nameIn.
-
-    (aName startsWith:'Smalltalk::') ifTrue:[
-	aName := aName copyFrom:12.
-	^ self at:(aName asSymbol) ifAbsent:nil.
-    ].
-
-    sym := aName asSymbol.
+    |nameUsed sym cls ns|
+
+    aName isNil ifTrue:[^ nil].
+    aName isBehavior ifTrue:[^ aName].       "/ already resolved
+    nameUsed := aName.
+
+    (nameUsed startsWith:'Smalltalk::') ifTrue:[
+        nameUsed := nameUsed copyFrom:12.
+        ^ self at:(nameUsed asSymbol) ifAbsent:nil.
+    ].
+
+    sym := nameUsed asSymbol.
 
     cls := aClass privateClassesAt:sym.
     cls notNil ifTrue:[^ cls].
 
     ns := aClass nameSpace.
     (ns notNil and:[ns ~~ Smalltalk]) ifTrue:[
-	ns isNameSpace ifTrue:[
-	    cls := ns at:sym ifAbsent:nil.
-	] ifFalse:[
-	    cls := ns privateClassesAt:sym
-	].
-	cls notNil ifTrue:[^ cls].
+        ns isNameSpace ifTrue:[
+            cls := ns at:sym ifAbsent:nil.
+        ] ifFalse:[
+            cls := ns privateClassesAt:sym
+        ].
+        cls notNil ifTrue:[^ cls].
     ].
     ^ self at:sym ifAbsent:nil.
 
@@ -8019,11 +8019,11 @@
 !Smalltalk class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.1036 2013-09-02 15:18:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.1037 2013-09-23 15:55:06 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.1036 2013-09-02 15:18:35 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/Smalltalk.st,v 1.1037 2013-09-23 15:55:06 cg Exp $'
 !
 
 version_HG
--- a/UserPreferences.st	Thu Sep 19 10:18:18 2013 +0100
+++ b/UserPreferences.st	Fri Sep 27 23:47:30 2013 +0100
@@ -3560,7 +3560,7 @@
 codeCompletionOnTabKey
     "show completion with TAB-key - experimental"                                                                 
 
-    ^ self at:#codeCompletionOnTabKey ifAbsent:false
+    ^ self at:#codeCompletionOnTabKey ifAbsent:true
 
     "
      UserPreferences current codeCompletionOnTabKey
@@ -4554,11 +4554,11 @@
 !UserPreferences class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.348 2013-09-04 22:03:11 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.349 2013-09-24 15:23:53 cg Exp $'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.348 2013-09-04 22:03:11 cg Exp $'
+    ^ '$Header: /cvs/stx/stx/libbasic/UserPreferences.st,v 1.349 2013-09-24 15:23:53 cg Exp $'
 !
 
 version_SVN