Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 20 Nov 2015 08:56:52 +0000
branchjv
changeset 18930 59e70e261e49
parent 18919 dbe023989a90 (current diff)
parent 18929 14b2c3ab66e8 (diff)
child 18942 b48824459593
Merge
CharacterArray.st
Date.st
ExternalStream.st
ProgrammingLanguage.st
Smalltalk.st
SmalltalkLanguage.st
UnixOperatingSystem.st
UserPreferences.st
--- a/CharacterArray.st	Thu Nov 19 06:41:24 2015 +0100
+++ b/CharacterArray.st	Fri Nov 20 08:56:52 2015 +0000
@@ -1210,7 +1210,7 @@
 !
 
 substrings
-    "return an array consisting of all words contained in the receiver.
+    "return a collection consisting of all words contained in the receiver.
      Words are separated by whitespace.
      This has been added for Squeak compatibility.
      (sigh: it is called #'subStrings' in V'Age, and #'asCollectionOfWords' in ST/X) "
@@ -1223,7 +1223,11 @@
 !
 
 substringsSeparatedBy:separatorCharacter
-    "Added for Squeak/Pharo compatibility"
+    "return a collection consisting of all words contained in the receiver.
+     Words are separated by the given separator character.   
+     This has been added for Squeak/Pharo compatibility.
+     (sigh: it is called #'subStrings:' in V'Age, 
+      and #'asCollectionOfSubstringsSeparatedBy' in ST/X) "
 
     ^ self asCollectionOfSubstringsSeparatedBy:separatorCharacter
 
@@ -1473,7 +1477,7 @@
 !
 
 subStrings
-    "return an array consisting of all words contained in the receiver.
+    "return a collection consisting of all words contained in the receiver.
      Words are separated by whitespace.
      This has been added for VisualAge compatibility.
      (sigh: it is called #'subbtrings' in Squeak, and #'asCollectionOfWords' in ST/X) "
@@ -1486,12 +1490,13 @@
 !
 
 subStrings:separatorCharacterOrString
-    "return an array consisting of all words contained in the receiver.
+    "return a collection consisting of all words contained in the receiver.
      Words are separated by separatorCharacter.
-     This is similar to split: and has been added for VisualAge compatibility."
+     This is similar to split: (squeak) and asCollectionOfSubstringsSeparatedBy: (st/x)
+     and has been added for VisualAge compatibility."
 
     separatorCharacterOrString isCharacter ifTrue:[
-	^ self asCollectionOfSubstringsSeparatedBy:separatorCharacterOrString
+        ^ self asCollectionOfSubstringsSeparatedBy:separatorCharacterOrString
     ].
     ^ self asCollectionOfSubstringsSeparatedByAny:separatorCharacterOrString
 
@@ -1504,7 +1509,7 @@
 
 trimSeparators
     "return a copy of the receiver without leading and trailing whiteSpace.
-     Added for VisualAge compatibility and an alias for withoutSeparators"
+     Added for VisualAge compatibility (an alias for withoutSeparators)"
 
     ^ self withoutSeparators
 ! !
--- a/Date.st	Thu Nov 19 06:41:24 2015 +0100
+++ b/Date.st	Fri Nov 20 08:56:52 2015 +0000
@@ -246,7 +246,7 @@
     ].
 
     Smalltalk addDependent:self.
-    Language ~= 'en' ifTrue:[
+    Smalltalk language ~= 'en' ifTrue:[
         EnvironmentChange := true
     ]
 ! !
@@ -1270,7 +1270,7 @@
     (DefaultFormats isNil or:[EnvironmentChange]) ifTrue:[
         self initNames
     ].
-    ^ DefaultFormats at:Language ifAbsent:(DefaultFormats at:#en).
+    ^ DefaultFormats at:Smalltalk language ifAbsent:(DefaultFormats at:#en).
 
     "
      Date today printStringFormat:(Date defaultFormatString).
@@ -1421,9 +1421,9 @@
 
 longFormatString
     (LongFormats isNil or:[EnvironmentChange]) ifTrue:[
-	self initNames
+        self initNames
     ].
-    ^ LongFormats at:Language ifAbsent:(LongFormats at:#en).
+    ^ LongFormats at:Smalltalk language ifAbsent:(LongFormats at:#en).
 
     "
      Date today printStringFormat:(Date defaultFormatString). 
@@ -1544,9 +1544,9 @@
 
 shortFormatString
     (ShortFormats isNil or:[EnvironmentChange]) ifTrue:[
-	self initNames
+        self initNames
     ].
-    ^ ShortFormats at:Language ifAbsent:(ShortFormats at:#en).
+    ^ ShortFormats at:Smalltalk language ifAbsent:(ShortFormats at:#en).
 
     "
      Date today printStringFormat:(Date defaultFormatString).
@@ -3600,12 +3600,13 @@
     "append a printed representation of the receiver to aStream.
      The argument languageOrNil can only be #en or nil for the current language."
 
-    |format|
+    |format langUsed|
 
     (DefaultFormats isNil or:[EnvironmentChange]) ifTrue:[
         self class initNames
     ].
-    format := DefaultFormats at:(languageOrNil ? Language) ifAbsent:[DefaultFormats at:#en].
+    langUsed := languageOrNil notNil ifTrue:[languageOrNil] ifFalse:[Smalltalk language].    
+    format := DefaultFormats at:langUsed ifAbsent:[DefaultFormats at:#en].
     self printOn:aStream format:format language:languageOrNil.
 
     "
--- a/ExternalStream.st	Thu Nov 19 06:41:24 2015 +0100
+++ b/ExternalStream.st	Fri Nov 20 08:56:52 2015 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
               All Rights Reserved
@@ -16,15 +14,15 @@
 "{ NameSpace: Smalltalk }"
 
 ReadWriteStream subclass:#ExternalStream
-        instanceVariableNames:'handleType handle mode buffered binary eolMode hitEOF didWrite
-                lastErrorNumber readAhead'
-        classVariableNames:'Lobby LastErrorNumber InvalidReadSignal InvalidWriteSignal
-                InvalidModeSignal OpenErrorSignal StreamNotOpenSignal
-                InvalidOperationSignal DefaultEOLMode ReadMode ReadWriteMode
-                WriteMode AppendMode CreateReadWriteMode StreamIOErrorSignal
-                FileOpenTrace MaxNonTenurableExecutors'
-        poolDictionaries:''
-        category:'Streams-External'
+	instanceVariableNames:'handleType handle mode buffered binary eolMode hitEOF didWrite
+		lastErrorNumber readAhead'
+	classVariableNames:'Lobby LastErrorNumber InvalidReadSignal InvalidWriteSignal
+		InvalidModeSignal OpenErrorSignal StreamNotOpenSignal
+		InvalidOperationSignal DefaultEOLMode ReadMode ReadWriteMode
+		WriteMode AppendMode CreateReadWriteMode StreamIOErrorSignal
+		FileOpenTrace MaxNonTenurableExecutors'
+	poolDictionaries:''
+	category:'Streams-External'
 !
 
 !ExternalStream primitiveDefinitions!
@@ -1579,7 +1577,10 @@
     ].
 
     "limit the amount of newspace to be used for non-tenurable executors to 5%"
-    MaxNonTenurableExecutors := ObjectMemory newSpaceSize // (Socket sizeOfInst:0) // 20.
+    "/ MaxNonTenurableExecutors := ObjectMemory newSpaceSize // (Socket sizeOfInst:0) // 20.
+    "/ cg: changed because Socket is not in libbasic. Thus, standalone (libbasic only)
+    "/ programs would fail to start.
+    MaxNonTenurableExecutors := (ObjectMemory newSpaceSize // 20 min:2000). 
 
     "Modified: / 21.5.1998 / 16:33:53 / cg"
 !
@@ -6300,7 +6301,7 @@
     ].
 
     "
-        'Bönnigheim' asUnicode16String errorPrintCR
+        'Bnnigheim' asUnicode16String errorPrintCR
     "
 !
 
@@ -6501,7 +6502,7 @@
     "
         (FileStream newTemporary
             nextPutUtf16:$B;
-            nextPutUtf16:$Ä;
+            nextPutUtf16:$;
             nextPutUtf16:(Character codePoint:16r10CCCC);
             reset;
             binary;
--- a/ProgrammingLanguage.st	Thu Nov 19 06:41:24 2015 +0100
+++ b/ProgrammingLanguage.st	Fri Nov 20 08:56:52 2015 +0000
@@ -474,6 +474,14 @@
 
 !ProgrammingLanguage methodsFor:'testing'!
 
+isGroovy
+    "true iff this is a Groovy language"
+
+    ^ false
+
+    "Created: / 13-04-2012 / 17:47:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 isJava
     "true iff this is the Java language"
 
@@ -482,6 +490,14 @@
     "Created: / 17-03-2011 / 10:16:23 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
 
+isJavaLike
+    "true if receiver is kind of Java language (based on Java)"
+
+    ^ false
+
+    "Created: / 13-04-2012 / 17:48:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+!
+
 isProgrammingLanguage
 
     ^true
--- a/Smalltalk.st	Thu Nov 19 06:41:24 2015 +0100
+++ b/Smalltalk.st	Fri Nov 20 08:56:52 2015 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -2452,8 +2450,8 @@
     | extensionsLoaded |
 
     extensionsLoaded := false.
-    ProgrammingLanguage allDo:[:lang|
-	extensionsLoaded := extensionsLoaded | (self loadExtensionsForPackage:aPackageId language: lang)
+    ProgrammingLanguage allDo:[:programmingLanguage|
+        extensionsLoaded := extensionsLoaded | (self loadExtensionsForPackage:aPackageId language: programmingLanguage)
     ].
     ^ extensionsLoaded
 
@@ -2462,81 +2460,81 @@
     "Modified (format): / 04-09-2011 / 09:19:24 / cg"
 !
 
-loadExtensionsForPackage:aPackageId language: language
+loadExtensionsForPackage:aPackageId language: programmingLanguage
     |mgr packageDirName inStream projectDefinition extensionsFilename mod dir
      extensionsRevisionString extensionsRevisionInfo|
 
-    language supportsExtensionMethods ifFalse:[^false].
+    programmingLanguage supportsExtensionMethods ifFalse:[^false].
 
     packageDirName := aPackageId copyReplaceAll:$: with:$/.
     packageDirName := self getPackageFileName:packageDirName.
 
     (packageDirName notNil and:[Class tryLocalSourceFirst]) ifTrue:[
-	(self loadExtensionsFromDirectory:packageDirName language: language) ifTrue:[
-	    ^ true.
-	].
-	packageDirName := nil.  "do not try again"
+        (self loadExtensionsFromDirectory:packageDirName language: programmingLanguage) ifTrue:[
+            ^ true.
+        ].
+        packageDirName := nil.  "do not try again"
     ].
 
     "
      if there is a sourceCodeManager, ask it first for the extensions
     "
     (Smalltalk at:#AbstractSourceCodeManager) notNil ifTrue:[
-	mgr := AbstractSourceCodeManager managerForPackage: aPackageId
+        mgr := AbstractSourceCodeManager managerForPackage: aPackageId
     ].
     mgr notNil ifTrue:[
-	extensionsFilename := 'extensions.' , language sourceFileSuffix.
-
-	projectDefinition := ProjectDefinition definitionClassForPackage:aPackageId.
-	projectDefinition notNil ifTrue:[
-	    mod := aPackageId asPackageId module.
-	    dir := aPackageId asPackageId directory.
-	    extensionsRevisionString := projectDefinition perform:(mgr nameOfVersionMethodForExtensions) ifNotUnderstood:nil.
-	    extensionsRevisionString notNil ifTrue:[
-		extensionsRevisionInfo := mgr revisionInfoFromString:extensionsRevisionString inClass:nil.
-		extensionsRevisionInfo notNil ifTrue:[
-		    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 |
-	    ] do:[
-		inStream := mgr streamForExtensionFile:extensionsFilename package:aPackageId directory:dir module:mod cache:true.
-	    ].
-	].
-	inStream isNil ifTrue:[
-	    SourceCodeManagerError handle:[:ex |
-	    ] do:[
-		inStream := mgr getMostRecentSourceStreamForFile:extensionsFilename inPackage:aPackageId.
-	    ].
-	].
-	inStream notNil ifTrue:[
-	    Class withoutUpdatingChangeSetDo:[
-		inStream fileIn.
-	    ].
-	    inStream close.
-	    VerboseLoading ifTrue:[
-		Transcript showCR:('loaded extensions for ',aPackageId,' from repository').
-	    ].
-	    ^ true
-	]
+        extensionsFilename := 'extensions.' , programmingLanguage sourceFileSuffix.
+
+        projectDefinition := ProjectDefinition definitionClassForPackage:aPackageId.
+        projectDefinition notNil ifTrue:[
+            mod := aPackageId asPackageId module.
+            dir := aPackageId asPackageId directory.
+            extensionsRevisionString := projectDefinition perform:(mgr nameOfVersionMethodForExtensions) ifNotUnderstood:nil.
+            extensionsRevisionString notNil ifTrue:[
+                extensionsRevisionInfo := mgr revisionInfoFromString:extensionsRevisionString inClass:nil.
+                extensionsRevisionInfo notNil ifTrue:[
+                    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: programmingLanguage
+                        ] ifFalse:[
+                            ^ false
+                        ]
+                    ]
+                ]
+            ].
+            SourceCodeManagerError handle:[:ex |
+            ] do:[
+                inStream := mgr streamForExtensionFile:extensionsFilename package:aPackageId directory:dir module:mod cache:true.
+            ].
+        ].
+        inStream isNil ifTrue:[
+            SourceCodeManagerError handle:[:ex |
+            ] do:[
+                inStream := mgr getMostRecentSourceStreamForFile:extensionsFilename inPackage:aPackageId.
+            ].
+        ].
+        inStream notNil ifTrue:[
+            Class withoutUpdatingChangeSetDo:[
+                inStream fileIn.
+            ].
+            inStream close.
+            VerboseLoading ifTrue:[
+                Transcript showCR:('loaded extensions for ',aPackageId,' from repository').
+            ].
+            ^ true
+        ]
     ].
 
     packageDirName notNil ifTrue:[
-	^ self loadExtensionsFromDirectory:packageDirName language: language
+        ^ self loadExtensionsFromDirectory:packageDirName language: programmingLanguage
     ].
     ^ false
 
@@ -2547,13 +2545,13 @@
 !
 
 loadExtensionsFromDirectory:packageDirOrString
-
     | extensionsLoaded |
+
     extensionsLoaded := false.
-    ProgrammingLanguage allDo:
-	[:lang|
-	extensionsLoaded := extensionsLoaded | (self loadExtensionsFromDirectory: packageDirOrString language: lang)].
-    ^extensionsLoaded
+    ProgrammingLanguage allDo:[:programmingLanguage|
+        extensionsLoaded := extensionsLoaded | (self loadExtensionsFromDirectory: packageDirOrString language: programmingLanguage)
+    ].
+    ^ extensionsLoaded
 
     "Modified: / 02-01-2010 / 10:40:33 / Jan Vrany <jan.vrany@fit.cvut.cz>"
 !
@@ -4979,9 +4977,11 @@
 languageTerritory:aTerritorySymbol
     "set the language territory - send out change notifications"
 
-    LanguageTerritory := aTerritorySymbol asSymbol.
-    self changed:#LanguageTerritory
-
+    aTerritorySymbol ~= LanguageTerritory ifTrue:[
+        LanguageTerritory := aTerritorySymbol asSymbol.
+        self changed:#LanguageTerritory
+    ].
+    
     "
      Time now
 
@@ -8111,35 +8111,35 @@
     "return a greeting string"
 
     "stupid: this should come from a resource file ...
-     but I dont use it here, to allow mini-systems without
+     but I don't use it here, to allow mini-systems without
      Resource-stuff."
 
     |proto lang|
 
     lang := Language.
     (lang == #de) ifTrue:[
-	proto := 'Willkommen bei %1 (Version %2 von %3)'
+        proto := 'Willkommen bei %1 (Version %2 von %3)'
     ] ifFalse:[ (lang == #fr) ifTrue:[
-	proto := 'Salut, Bienvenue à %1 (version %2 de %3)'
+        proto := 'Salut, Bienvenue à %1 (version %2 de %3)'
     ] ifFalse:[ (lang == #it) ifTrue:[
-	proto := 'Ciao, benvenuto al %1 (versione %2 di %3)'
+        proto := 'Ciao, benvenuto al %1 (versione %2 di %3)'
     ] ifFalse:[ (lang == #es) ifTrue:[
-"/        proto := 'Hola, bienvenida a %1 (versión %2 de %3)'
-    ] ifFalse:[ (lang == #es) ifTrue:[
-"/        proto := 'Oi, benvindo a %1 (versão %2 de %3)'
+        proto := 'Hola, bienvenida a %1 (version %2 de %3)'
+    ] ifFalse:[ (lang == #pt) ifTrue:[
+        proto := 'Ol!!, mem-vindo a %1 (version %2 de %3)'
     ] ifFalse:[ (lang == #no) ifTrue:[
-	proto := 'Hei, verdenmottakelse til %1 (versjon %2 av %3)'
+        proto := 'Hei, verdenmottakelse til %1 (versjon %2 av %3)'
     ]]]]]].
 
     "/ ... more needed here ...
 
     proto isNil ifTrue:[
-	proto := 'Hello World - here is %1 version %2 of %3'.
+        proto := 'Hello World - welcome to %1 version %2 of %3'.
     ].
 
     ^ proto bindWith:('Smalltalk/X jv-branch' allBold)
-		with:(self versionString)
-		with:(self versionDate)
+                with:(self versionString)
+                with:(self versionDate)
 
     "
      Smalltalk language:#us.
--- a/SmalltalkLanguage.st	Thu Nov 19 06:41:24 2015 +0100
+++ b/SmalltalkLanguage.st	Fri Nov 20 08:56:52 2015 +0000
@@ -126,11 +126,12 @@
      as 'Smalltalk language' is used by legacy code to access
      the current language setting. 
      Future versions should contain class Locale.
+     cg: this is crab, who needs this?
     "
     <resource: #obsolete>
 
     self obsoleteMethodWarning.
-    ^ Language , anObject
+    ^ Smalltalk language , anObject
 
     "Created: / 22-08-2009 / 09:33:44 / Jan Vrany <vranyj1@fel.cvut.cz>"
     "Modified (comment): / 01-04-2012 / 13:19:28 / cg"
@@ -141,11 +142,12 @@
      as Smalltalk language is used by legacy code to access
      current language. Future versions should contain class
      Locale.
+     cg: this is crab, who needs this?
     "
     <resource: #obsolete>
 
     self obsoleteMethodWarning.
-    ^ Language
+    ^ Smalltalk language
 
     "Created: / 22-08-2009 / 09:33:16 / Jan Vrany <vranyj1@fel.cvut.cz>"
 ! !
--- a/UnixOperatingSystem.st	Thu Nov 19 06:41:24 2015 +0100
+++ b/UnixOperatingSystem.st	Fri Nov 20 08:56:52 2015 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -625,7 +623,6 @@
 ! !
 
 !UnixOperatingSystem primitiveFunctions!
-
 %{
 
 /*
@@ -1962,9 +1959,9 @@
     "open a windows-shell/mac finder/desktop application to present the document contained in aFilenameOrString.
      This is typically used to present help-files, html documents, pdf documents etc.
      operationSymbol is one of:
-	open
-	edit
-	explore
+        open
+        edit
+        explore
      mimeTypeStringArgOrNil is e.g. 'text/html' or: 'application/pdf';
      if nil is passed in, the file's suffix is used to guess it.
     "
@@ -1973,16 +1970,16 @@
 
     cmd := self openApplicationHelperCommand.
     cmd notNil ifTrue:[
-	(cmd includesSubString:'%1') ifTrue:[
-	    cmd := cmd bindWith:aFilenameOrString asString.
-	] ifFalse:[
-	    cmd := cmd, ' "', aFilenameOrString asString, '"'.
-	].
-	(self
-		startProcess:cmd
-		inputFrom:nil outputTo:nil
-		errorTo:nil auxFrom:nil
-		environment: self getEnvironment inDirectory:nil) notNil ifTrue:[ ^ self ]
+        (cmd includesSubString:'%1') ifTrue:[
+            cmd := cmd bindWith:aFilenameOrString asString.
+        ] ifFalse:[
+            cmd := cmd, ' "', aFilenameOrString asString, '"'.
+        ].
+        (self
+            startProcess:cmd
+            inputFrom:nil outputTo:nil
+            errorTo:nil auxFrom:nil
+            environment: self getEnvironment inDirectory:nil) notNil ifTrue:[ ^ self ]
     ].
     ^ super openApplicationForDocument:aFilenameOrString operation:operationSymbol mimeType:mimeTypeStringArgOrNil ifNone:exceptionBlock
 
@@ -2001,18 +1998,26 @@
 openApplicationHelperCommand
     "Return a command line helper to open a default application for file or URL"
 
-    | xdgCurrentDesktop |
+    | xdgCurrentDesktop usersPref |
+
+    ((usersPref := UserPreferences current osFileExplorerCommand) notEmptyOrNil
+    and:[ self canExecuteCommand:(usersPref subStrings first) ]) ifTrue:[
+        ^ usersPref
+    ].    
 
     xdgCurrentDesktop := self getEnvironment: 'XDG_CURRENT_DESKTOP'.
     ((xdgCurrentDesktop = 'GNOME') and:[self canExecuteCommand: 'gnome-open']) ifTrue:[
-	^ 'gnome-open'
+        ^ 'gnome-open'
     ].
     "/ Guess...
     ((xdgCurrentDesktop = 'KDE') and:[self canExecuteCommand: 'kde-open']) ifTrue:[
-	^ 'kde-open'
+        ^ 'kde-open'
     ].
     (self canExecuteCommand: 'xdg-open') ifTrue:[
-	^ 'xdg-open'
+        ^ 'xdg-open'
+    ].
+    (self canExecuteCommand: 'nautilus') ifTrue:[
+        ^ 'nautilus'
     ].
     ^ nil
 
@@ -2024,7 +2029,6 @@
     "
 
     "Created: / 13-01-2015 / 09:02:07 / Jan Vrany <jan.vrany@fit.cvut.cz>"
-
 ! !
 
 !UnixOperatingSystem class methodsFor:'error messages'!
@@ -9536,7 +9540,7 @@
      Codeset := #'utf8-mac'.
      CodesetEncoder := nil.
      OperatingSystem getCodesetEncoder
-     OperatingSystem encodePath:'äöü'
+     OperatingSystem encodePath:''
     "
 
     "Modified: / 23-01-2013 / 10:00:11 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -13061,7 +13065,7 @@
 	    domain:#'AF_INET' type:nil protocol:nil flags:nil
      self getAddressInfo:'www.exept.de' serviceName:nil
 	    domain:#'AF_INET6' type:nil protocol:nil flags:nil
-     self getAddressInfo:'www.baden-württemberg.de' serviceName:nil
+     self getAddressInfo:'www.baden-wrttemberg.de' serviceName:nil
 	    domain:#'AF_INET' type:#stream protocol:nil flags:nil
     "
 !
--- a/UserPreferences.st	Thu Nov 19 06:41:24 2015 +0100
+++ b/UserPreferences.st	Fri Nov 20 08:56:52 2015 +0000
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1998 by eXept Software AG
 	      All Rights Reserved
@@ -843,6 +841,15 @@
 
 
 
+!UserPreferences methodsFor:'accessing-changes & history'!
+
+historyManagerAllowEditOfHistory:aBoolean
+    "useful if you have 'beginner students', to prevent them from changing the history"
+
+    self 
+        at: #'history-manager.allow-edit-of-history'
+        put:aBoolean
+! !
 
 !UserPreferences methodsFor:'accessing-locale'!
 
@@ -899,17 +906,17 @@
      This is rather user setting. To ask whether the selector namespaces
      support should be used, use:
 
-	UserPreferences current selectorNamespacesSupportedAndEnabled
-    "
-
-    ^self at:#selectorNamespacesEnabled ifAbsent:[false].
-
-    "
-	UserPreferences current selectorNamespacesEnabled
-	UserPreferences current selectorNamespacesSupportedAndEnabled
-
-	UserPreferences current selectorNamespacesEnabled: true.
-	UserPreferences current selectorNamespacesEnabled: false.
+        UserPreferences current selectorNamespacesSupportedAndEnabled
+    "
+
+    ^self at:#selectorNamespacesEnabled ifAbsent:false.
+
+    "
+        UserPreferences current selectorNamespacesEnabled
+        UserPreferences current selectorNamespacesSupportedAndEnabled
+
+        UserPreferences current selectorNamespacesEnabled: true.
+        UserPreferences current selectorNamespacesEnabled: false.
     "
 
     "Created: / 19-07-2012 / 15:26:04 / Jan Vrany <jan.vrany@fit.cvut.cz>"
@@ -4609,6 +4616,31 @@
     "Created: / 03-07-2006 / 16:50:20 / cg"
 ! !
 
+!UserPreferences methodsFor:'accessing-prefs-external tools'!
+
+osFileExplorerCommand
+    "return an OS command template to open a finder/explorer or similar"
+
+    ^ self at:#osFileExplorerCommand ifAbsent:nil
+!
+
+osFileExplorerCommand:aString
+    "define an OS command template to open a finder/explorer or similar"
+
+    self at:#osFileExplorerCommand put:aString
+
+    "
+     UserPreferences current osFileExplorerCommand
+     
+     osx:
+     UserPreferences current osFileExplorerCommand:'open %1'
+     
+     linux:
+     UserPreferences current osFileExplorerCommand:'nautilus %1'
+     UserPreferences current osFileExplorerCommand:'dolphin %1'
+    "
+! !
+
 !UserPreferences methodsFor:'accessing-prefs-files and directories'!
 
 changeFileName