Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Mon, 18 Apr 2016 07:17:25 +0100
branchjv
changeset 19610 a9a6940944a9
parent 19609 2e84112b362b (current diff)
parent 19599 04c6b041e116 (diff)
child 19611 b1aaf1175f51
Merge
ApplicationDefinition.st
CharacterArray.st
Collection.st
Filename.st
Method.st
Object.st
ObjectCoder.st
PCFilename.st
PositionableStream.st
ProjectDefinition.st
Smalltalk.st
StandaloneStartup.st
String.st
TwoByteString.st
UserPreferences.st
Win32OperatingSystem.st
stx_libbasic.st
--- a/ApplicationDefinition.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/ApplicationDefinition.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1860,12 +1860,12 @@
 
 setup: $(PROJECT) postBuildCleanup %(NSI_FILENAME) 
         $(MAKENSIS) /DOBJ_DIR=objmingw /DSETUP_NAME=%(PRODUCT_NAME)Setup64 %(NSI_FILENAME)
-        %(ADDITIONAL_POSTNSISRULES)
+        %(ADDITIONAL_POSTNSISRULES64)
 
 !!else
 
 setup: $(PROJECT) postBuildCleanup %(NSI_FILENAME)
-        $(MAKENSIS) /DOBJ_DIR=objmingw /DSETUP_NAME=%(PRODUCT_NAME)Setup %(NSI_FILENAME)
+        $(MAKENSIS) /DOBJ_DIR=objbc /DSETUP_NAME=%(PRODUCT_NAME)Setup %(NSI_FILENAME)
         %(ADDITIONAL_POSTNSISRULES)
 
 !!endif
--- a/CharacterArray.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/CharacterArray.st	Mon Apr 18 07:17:25 2016 +0100
@@ -5845,6 +5845,7 @@
     "Modified: 17.4.1997 / 12:50:23 / cg"
 ! !
 
+
 !CharacterArray methodsFor:'special string converting'!
 
 asUnixFilenameString
@@ -7572,10 +7573,12 @@
 !
 
 isWideString
+    "true if I require more than one byte per character"
+    
     |string|
 
     (string := self string) ~~ self ifTrue:[
-	^ string isWideString.
+        ^ string isWideString.
     ].
     ^ self contains:[:aCharacter | aCharacter codePoint > 16rFF].
 !
--- a/Collection.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/Collection.st	Mon Apr 18 07:17:25 2016 +0100
@@ -5370,7 +5370,9 @@
                 eachChild := graphEntry at:i.
                 (backTrace includesIdentical:eachChild) ifTrue:[
                     backTrace add:eachChild.
-                    self error:('cycle in ordering: %1' bindWith:backTrace reversed) mayProceed:true.
+                    ProceedableError
+                        raiseRequestWith:backTrace reversed
+                        errorString:('cycle in ordering: %1' bindWith:(backTrace reversed printStringWithSeparator:' -> ')).
                 ].
                 eachChildGraph := graph at:eachChild.
                 checkBlock value:eachChildGraph value:(backTrace copyWith:eachChild).
@@ -5875,6 +5877,7 @@
     ^ aVisitor visitCollection:self with:aParameter
 ! !
 
+
 !Collection class methodsFor:'documentation'!
 
 version
--- a/Filename.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/Filename.st	Mon Apr 18 07:17:25 2016 +0100
@@ -629,29 +629,29 @@
     |nameString newTempFilename|
 
     self isAbstract ifTrue:[
-        ^ ConcreteClass newTemporaryIn:aDirectoryOrNil nameTemplate:template
+	^ ConcreteClass newTemporaryIn:aDirectoryOrNil nameTemplate:template
     ].
 
     "although the above allows things to be redefined in concrete classes,
      the following should work on all systems ..."
 
     [
-        "Use random numbers in order to improve the security
-         by making the generated names less predictable"
-        nameString := template bindWith:(OperatingSystem getProcessId) with:(RandomGenerator nextLettersOrDigits:4).
-
-        aDirectoryOrNil isNil ifTrue:[
-            newTempFilename := self named:nameString
-        ] ifFalse:[
-            newTempFilename := aDirectoryOrNil asFilename construct:nameString
-        ]
+	"Use random numbers in order to improve the security
+	 by making the generated names less predictable"
+	nameString := template bindWith:(OperatingSystem getProcessId) with:(RandomGenerator nextLettersOrDigits:4).
+
+	aDirectoryOrNil isNil ifTrue:[
+	    newTempFilename := self named:nameString
+	] ifFalse:[
+	    newTempFilename := aDirectoryOrNil asFilename construct:nameString
+	]
     ] doWhile:[
-        "care for existing leftOver tempFiles
-         from a previous boot of the OS
-         i.e. my pid could be the same as when executed
-         the last time before system reboot ...)"
-
-        newTempFilename exists
+	"care for existing leftOver tempFiles
+	 from a previous boot of the OS
+	 i.e. my pid could be the same as when executed
+	 the last time before system reboot ...)"
+
+	newTempFilename exists
     ].
     ^ newTempFilename
 
@@ -810,22 +810,22 @@
      otherwise, '/tmp' is used. (at least on unix ...).
 
      Notice: do not hardcode '/tmp' into your programs - things may be
-             different on other operating systems. Also, the user may want to set the
-             TMPDIR environment variable to have her temp files somewhere else."
+	     different on other operating systems. Also, the user may want to set the
+	     TMPDIR environment variable to have her temp files somewhere else."
 
     |tempDir|
 
     TempDirectory isNil ifTrue:[
-        tempDir := self named:(self defaultTempDirectoryName pathName).
-        tempDir exists ifFalse:[
-            tempDir
-                makeDirectory;
-                addAccessRights:#(readUser readGroup readOthers
-                                  writeUser writeGroup writeOthers
-                                  executeUser executeGroup executeOthers
-                                  removeOnlyByOwner).
-        ].
-        TempDirectory := DefaultTempDirectory := tempDir construct:'stx_tmp'.
+	tempDir := self named:(self defaultTempDirectoryName pathName).
+	tempDir exists ifFalse:[
+	    tempDir
+		makeDirectory;
+		addAccessRights:#(readUser readGroup readOthers
+				  writeUser writeGroup writeOthers
+				  executeUser executeGroup executeOthers
+				  removeOnlyByOwner).
+	].
+	TempDirectory := DefaultTempDirectory := tempDir construct:'stx_tmp'.
     ].
 
     "Make sure, that the TempDirectory exists - it might have been removed
@@ -833,12 +833,12 @@
      Since it is shared between users, it must be accessible by all users."
 
     TempDirectory exists ifFalse:[
-        TempDirectory
-            makeDirectory;
-            addAccessRights:#(readUser readGroup readOthers
-                              writeUser writeGroup writeOthers
-                              executeUser executeGroup executeOthers
-                              removeOnlyByOwner).
+	TempDirectory
+	    makeDirectory;
+	    addAccessRights:#(readUser readGroup readOthers
+			      writeUser writeGroup writeOthers
+			      executeUser executeGroup executeOthers
+			      removeOnlyByOwner).
     ].
     ^ TempDirectory
 
@@ -864,8 +864,8 @@
     |temp|
 
     aFilename isNil ifTrue:[
-        TempDirectory := nil.
-        ^ self.
+	TempDirectory := nil.
+	^ self.
     ].
 
     temp := aFilename asFilename.
@@ -940,6 +940,10 @@
     "Modified: 7.9.1995 / 10:48:31 / claus"
     "Created: 7.3.1996 / 14:51:18 / cg"
     "Modified: 8.9.1997 / 00:24:53 / cg"
+!
+
+defaultVolumeName
+    ^ '/'
 ! !
 
 !Filename class methodsFor:'misc'!
@@ -2158,9 +2162,9 @@
      So users of this method better test for existing directory before."
 
     self directoryContentsAsFilenamesDo:[:eachFileOrDirectory |
-        eachFileOrDirectory isDirectory ifTrue:[
-            aBlock value:eachFileOrDirectory
-        ]
+	eachFileOrDirectory isDirectory ifTrue:[
+	    aBlock value:eachFileOrDirectory
+	]
     ].
 
     "
@@ -2234,7 +2238,7 @@
 !
 
 files
-    "return a collection of regular files   
+    "return a collection of regular files
      contained in the directory represented by the receiver."
 
     |collection|
@@ -2255,9 +2259,9 @@
      contained in the directory represented by the receiver."
 
     ^ self directoryContentsAsFilenamesDo:[:eachFileOrDirectory |
-        eachFileOrDirectory isRegularFile ifTrue:[ 
-            aBlock value: eachFileOrDirectory
-        ].
+	eachFileOrDirectory isRegularFile ifTrue:[
+	    aBlock value: eachFileOrDirectory
+	].
     ].
 
     "
@@ -2270,7 +2274,7 @@
 
 filesWithSuffix:suffix
     "return a collection of regular files (i.e. not subdirectories)
-     with a given suffix which are contained in the directory 
+     with a given suffix which are contained in the directory
      represented by the receiver."
 
     |collection|
@@ -2290,11 +2294,11 @@
      (i.e. subdirs are ignored)"
 
     ^ self directoryContentsAsFilenamesDo:[:eachFileOrDirectory |
-        (eachFileOrDirectory hasSuffix:suffix) ifTrue:[
-            eachFileOrDirectory isRegularFile ifTrue:[ 
-                aBlock value: eachFileOrDirectory
-            ].
-        ].
+	(eachFileOrDirectory hasSuffix:suffix) ifTrue:[
+	    eachFileOrDirectory isRegularFile ifTrue:[
+		aBlock value: eachFileOrDirectory
+	    ].
+	].
     ].
 
     "
@@ -2352,27 +2356,27 @@
     fileNames := OrderedCollection new.
     dirNames := OrderedCollection new.
     self directoryContentsDo:[:f | |t|
-        t := self construct:f.
-        t isDirectory ifTrue:[
-            t isSymbolicLink ifFalse:[
-                dirNames add:f
-            ]
-        ] ifFalse:[
-            fileNames add:f
-        ]
+	t := self construct:f.
+	t isDirectory ifTrue:[
+	    t isSymbolicLink ifFalse:[
+		dirNames add:f
+	    ]
+	] ifFalse:[
+	    fileNames add:f
+	]
     ].
 
     aPrefix size > 0 ifTrue:[
-        p := aPrefix , self separator
+	p := aPrefix , self separator
     ] ifFalse:[
-        p := ''
+	p := ''
     ].
 
     fileNames do:[:aFile | aBlock value:(p , aFile)].
     dirNames do:[:dN |
-        aBlock value:(p , dN).
-        (self construct:dN)
-            recursiveDirectoryContentsDo:aBlock directoryPrefix:(p , dN)
+	aBlock value:(p , dN).
+	(self construct:dN)
+	    recursiveDirectoryContentsDo:aBlock directoryPrefix:(p , dN)
     ].
 
     "
@@ -3043,17 +3047,17 @@
     |writeStream|
 
     self exists ifTrue:[
-        OperatingSystem accessDeniedErrorSignal
-            raiseRequestWith:self
-            errorString:(' - file exists: ' , self asString).
-        ^ self
+	OperatingSystem accessDeniedErrorSignal
+	    raiseRequestWith:self
+	    errorString:(' - file exists: ' , self asString).
+	^ self
     ].
 
     FileStream openErrorSignal handle:[:ex|
-        self fileCreationError:self.
-        ^ self
+	self fileCreationError:self.
+	^ self
     ] do:[
-        writeStream := self newReadWriteStream.
+	writeStream := self newReadWriteStream.
     ].
     writeStream close.
 !
@@ -3065,7 +3069,7 @@
     OperatingSystem createSymbolicLinkFrom:linkFilenameString to:self pathName.
 
     "
-        '/tmp/link' asFilename makeSymbolicLinkTo:'bla'
+	'/tmp/link' asFilename makeSymbolicLinkTo:'bla'
     "
 !
 
@@ -3080,13 +3084,13 @@
      Raises an exception if not successful"
 
     (self basicMakeDirectory) ifFalse:[
-        "/
-        "/ could have existed before ...
-        "/
-        (self exists and:[self isDirectory]) ifFalse:[
-            self fileCreationError:self.
-            ^ false
-        ]
+	"/
+	"/ could have existed before ...
+	"/
+	(self exists and:[self isDirectory]) ifFalse:[
+	    self fileCreationError:self.
+	    ^ false
+	]
     ].
     ^ true
 
@@ -3186,11 +3190,11 @@
 
     destinationFilename := destination asFilename.
     self isDirectory ifFalse:[
-        destinationFilename isDirectory ifTrue:[
-            destinationFilename := destinationFilename construct:self baseName.
-        ].
-        self copyTo:destinationFilename.
-        ^ self.
+	destinationFilename isDirectory ifTrue:[
+	    destinationFilename := destinationFilename construct:self baseName.
+	].
+	self copyTo:destinationFilename.
+	^ self.
     ].
 
     "/ typically, an 'cp -r' is faster;
@@ -3198,15 +3202,15 @@
     "/ fallBack doing a manual directory walk.
 
     ok := OperatingSystem
-            recursiveCopyDirectory:(self osNameForDirectory)
-            to:(destinationFilename osNameForDirectory).
+	    recursiveCopyDirectory:(self osNameForDirectory)
+	    to:(destinationFilename osNameForDirectory).
 
     ok ifFalse:[
-        self recursiveCopyWithoutOSCommandTo:destinationFilename
-    ].
-
-    "
-        '.' asFilename recursiveCopyTo:'/temp/xxx'.
+	self recursiveCopyWithoutOSCommandTo:destinationFilename
+    ].
+
+    "
+	'.' asFilename recursiveCopyTo:'/temp/xxx'.
     "
 
     "Created: / 05-05-1999 / 13:35:01 / cg"
@@ -3229,33 +3233,33 @@
     destinationFilename := destination asFilename.
 
     self isDirectory ifTrue:[
-        destinationFilename exists ifFalse:[
-            destinationFilename makeDirectory.
-            destinationFilename accessRights:self accessRights.
-        ].
-
-        self directoryContentsDo:[:aFilenameString |
-            |src srcInfo dst info|
-
-            src := self construct:aFilenameString.
-            dst := destinationFilename construct:aFilenameString.
-
-            srcInfo := src linkInfo.
-            srcInfo isDirectory ifTrue:[
-                src recursiveCopyWithoutOSCommandTo:dst
-            ] ifFalse:[srcInfo isSymbolicLink ifTrue:[
-                dst
-                    remove;
-                    createAsSymbolicLinkTo:src linkInfo path.
-            ] ifFalse:[
-                src copyTo:dst.
-            ]].
-        ].
+	destinationFilename exists ifFalse:[
+	    destinationFilename makeDirectory.
+	    destinationFilename accessRights:self accessRights.
+	].
+
+	self directoryContentsDo:[:aFilenameString |
+	    |src srcInfo dst info|
+
+	    src := self construct:aFilenameString.
+	    dst := destinationFilename construct:aFilenameString.
+
+	    srcInfo := src linkInfo.
+	    srcInfo isDirectory ifTrue:[
+		src recursiveCopyWithoutOSCommandTo:dst
+	    ] ifFalse:[srcInfo isSymbolicLink ifTrue:[
+		dst
+		    remove;
+		    createAsSymbolicLinkTo:src linkInfo path.
+	    ] ifFalse:[
+		src copyTo:dst.
+	    ]].
+	].
     ] ifFalse:[
-        destinationFilename isDirectory ifTrue:[
-            destinationFilename := destinationFilename construct:self baseName.
-        ].
-        self copyTo:destinationFilename.
+	destinationFilename isDirectory ifTrue:[
+	    destinationFilename := destinationFilename construct:self baseName.
+	].
+	self copyTo:destinationFilename.
     ]
 
     "
@@ -3306,7 +3310,7 @@
 
     ok := OperatingSystem recursiveRemoveDirectory:(self osNameForDirectory).
     ok ifFalse:[
-        self recursiveRemoveWithoutOSCommand
+	self recursiveRemoveWithoutOSCommand
     ].
 
     "
@@ -3334,23 +3338,23 @@
     |removeFailedError|
 
     self isDirectory ifTrue:[
-        removeFailedError := OperatingSystem accessDeniedErrorSignal.
-        self directoryContentsAsFilenamesDo:[:eachFilename |
-            removeFailedError handle:[:ex |
-                eachFilename isDirectory ifFalse:[ ex reject ].
-                eachFilename            
-                    recursiveRemoveAll;
-                    removeDirectory.
-            ] do:[
-                eachFilename remove
-            ].
+	removeFailedError := OperatingSystem accessDeniedErrorSignal.
+	self directoryContentsAsFilenamesDo:[:eachFilename |
+	    removeFailedError handle:[:ex |
+		eachFilename isDirectory ifFalse:[ ex reject ].
+		eachFilename
+		    recursiveRemoveAll;
+		    removeDirectory.
+	    ] do:[
+		eachFilename remove
+	    ].
 
 "/            eachFilename isDirectory ifTrue:[
 "/                eachFilename recursiveRemoveWithoutOSCommand
 "/            ] ifFalse:[
 "/                eachFilename remove
 "/            ].
-        ]
+	]
     ].
 
     "
@@ -3404,18 +3408,18 @@
     osName := self osNameForAccess.
     ok := OperatingSystem removeFile:osName.
     ok ifFalse:[
-        linkInfo := self linkInfo.
-        linkInfo isNil ifTrue:[
-            "file does not exist - no error"
-            ^ self.
-        ] ifFalse:[linkInfo isDirectory ifTrue:[
-            ok := OperatingSystem removeDirectory:osName
-        ]].
-        ok ifFalse:[
-            self exists ifTrue:[
-                self removeError:self pathName
-            ]
-        ]
+	linkInfo := self linkInfo.
+	linkInfo isNil ifTrue:[
+	    "file does not exist - no error"
+	    ^ self.
+	] ifFalse:[linkInfo isDirectory ifTrue:[
+	    ok := OperatingSystem removeDirectory:osName
+	]].
+	ok ifFalse:[
+	    self exists ifTrue:[
+		self removeError:self pathName
+	    ]
+	]
     ].
 
     "
@@ -3441,8 +3445,8 @@
      Use #recursiveRemove in order to (recursively) remove non empty directories."
 
     (OperatingSystem removeDirectory:(self osNameForAccess)) ifFalse:[
-        self exists ifFalse:[ ^ self].
-        self removeError:self
+	self exists ifFalse:[ ^ self].
+	self removeError:self
     ].
 
     "
@@ -3459,7 +3463,7 @@
      'foo' asFilename makeDirectory.
      'foo/bar' asFilename writeStream close.
      ('foo' asFilename remove) ifFalse:[
-        Transcript showCR:'could not remove foo'
+	Transcript showCR:'could not remove foo'
      ]
     "
 
@@ -3474,9 +3478,9 @@
      Use #recursiveRemove in order to (recursively) remove non empty directories."
 
     (OperatingSystem removeFile:self osNameForAccess) ifFalse:[
-        self exists ifTrue:[
-            self removeError:self
-        ].
+	self exists ifTrue:[
+	    self removeError:self
+	].
     ].
 
     "
@@ -5042,19 +5046,19 @@
     otherNames := self class canonicalizedNameComponents:filenameArg name.
     myNames := self class canonicalizedNameComponents:self name.
     ((otherNames startsWith:myNames) and:[myNames first ~= self class parentDirectoryName]) ifTrue:[
-        ^ otherNames ~= myNames
+	^ otherNames ~= myNames
     ].
 
     "fall back - try it again with ~ substitution and symbolic links resolved"
     otherNames := self class canonicalizedNameComponents:filenameArg pathName.
     myNames := self class canonicalizedNameComponents:self pathName.
     (otherNames startsWith:myNames) ifTrue:[
-        ^ otherNames ~= myNames
+	^ otherNames ~= myNames
     ].
 
     myName := self class nameFromComponents:myNames.
     filenameArg allParentDirectoriesDo:[:parent |
-        parent pathName = myName ifTrue:[^ true].
+	parent pathName = myName ifTrue:[^ true].
     ].
     ^ false.
 
@@ -5210,7 +5214,7 @@
 
     pathOrNil := self physicalPathName.
     pathOrNil isNil ifTrue:[
-        ^ nil
+	^ nil
     ].
     ^ pathOrNil asFilename
 
@@ -5230,30 +5234,30 @@
 
     info := self linkInfo.
     info isNil ifTrue:[
-        " I do not exist"
-        ^ nil.
+	" I do not exist"
+	^ nil.
     ].
     info isSymbolicLink ifFalse:[
-        ^ self pathName
+	^ self pathName
     ].
 
     t := self.
     [
-        path := info path.
-        path isNil ifTrue:[
-            "/ cannot happen
-            ^ nil
-        ].
-        path asFilename isAbsolute ifTrue:[
-            t := path asFilename
-        ] ifFalse:[
-            t := (self species named:t directoryName) construct:path.
-        ].
-        info := t linkInfo.
-        info isNil ifTrue:[
-            "t does not exist"
-             ^ nil
-        ].
+	path := info path.
+	path isNil ifTrue:[
+	    "/ cannot happen
+	    ^ nil
+	].
+	path asFilename isAbsolute ifTrue:[
+	    t := path asFilename
+	] ifFalse:[
+	    t := (self species named:t directoryName) construct:path.
+	].
+	info := t linkInfo.
+	info isNil ifTrue:[
+	    "t does not exist"
+	     ^ nil
+	].
     ] doWhile:[info isSymbolicLink].
 
     ^ t pathName
@@ -5817,13 +5821,13 @@
 
     prefixName := self name.
     aSuffix isEmptyOrNil ifTrue:[
-        ^ self species named:prefixName
+	^ self species named:prefixName
     ].
 
     ^ self species named:
-        (prefixName
-         , self species suffixSeparator asString
-         , aSuffix asString)
+	(prefixName
+	 , self species suffixSeparator asString
+	 , aSuffix asString)
 
     "
      'abc.st' asFilename addSuffix:nil
@@ -6010,13 +6014,13 @@
 
     prefixName := self nameWithoutSuffix.
     aSuffix isEmptyOrNil ifTrue:[
-        ^ self species named:prefixName
+	^ self species named:prefixName
     ].
 
     ^ self species named:
-        (prefixName
-         , self class suffixSeparator asString
-         , aSuffix asString)
+	(prefixName
+	 , self class suffixSeparator asString
+	 , aSuffix asString)
 
     "
      'abc.st' asFilename withSuffix:nil
@@ -6104,16 +6108,16 @@
 
     stream := self appendStream.
     [
-        result := aBlock value:stream
+	result := aBlock value:stream
     ] ensure:[
-        stream close
+	stream close
     ].
     ^ result
 
     "
      'ttt' asFilename appendingFileDo:[:s |
-        s nextPutLine:'hello'.
-        s nextPutLine:'world'.
+	s nextPutLine:'hello'.
+	s nextPutLine:'world'.
      ]
     "
 
@@ -6158,16 +6162,16 @@
 
     stream := self writeStream.
     [
-        result := aBlock value:stream
+	result := aBlock value:stream
     ] ensure:[
-        stream close
+	stream close
     ].
     ^ result
 
     "
      'ttt' asFilename writingFileDo:[:s |
-        s nextPutLine:'hello'.
-        s nextPutLine:'world'.
+	s nextPutLine:'hello'.
+	s nextPutLine:'world'.
      ]
     "
 
--- a/Method.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/Method.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1028,9 +1028,11 @@
 
 annotationsAt: key1 orAt: key2 do: block
     self annotationsDo:[:annot |
-	(annot key == key1 or:[annot key == key2]) ifTrue:[
-	    block value: annot
-	]
+        |key|
+        key := annot key.
+        (key == key1 or:[key == key2]) ifTrue:[
+            block value: annot
+        ]
     ]
 
     "Created: / 16-07-2010 / 11:47:20 / Jan Vrany <jan.vrany@fit.cvut.cz>"
--- a/Object.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/Object.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -258,6 +256,7 @@
     "Modified: / 4.8.1999 / 08:54:06 / stefan"
 ! !
 
+
 !Object class methodsFor:'Compatibility-ST80'!
 
 rootError
@@ -496,6 +495,7 @@
     InfoPrinting := aBoolean
 ! !
 
+
 !Object class methodsFor:'queries'!
 
 isAbstract
@@ -519,6 +519,8 @@
 
 
 
+
+
 !Object methodsFor:'Compatibility-Dolphin'!
 
 stbFixup: anSTBInFiler at: newObjectIndex
@@ -1757,6 +1759,8 @@
     "
 ! !
 
+
+
 !Object methodsFor:'attributes access'!
 
 objectAttributeAt:attributeKey
@@ -1879,6 +1883,7 @@
 ! !
 
 
+
 !Object methodsFor:'change & update'!
 
 broadcast:aSelectorSymbol
@@ -1980,11 +1985,11 @@
 
 changed:aParameter with:anArgument
     "notify all dependents that the receiver has changed somehow.
-     Each dependent gets a  '#update:with:from:'-message, with aParameter
+     Each dependent gets an '#update:with:from:'-message, with aParameter
      and anArgument as arguments."
 
     self dependentsDo:[:dependent |
-	dependent update:aParameter with:anArgument from:self
+        dependent update:aParameter with:anArgument from:self
     ]
 !
 
@@ -2059,6 +2064,7 @@
     ^ aBlock ensure:[ self addDependent:someone ]
 ! !
 
+
 !Object methodsFor:'comparing'!
 
 = anObject
@@ -7983,6 +7989,7 @@
     ^ self
 ! !
 
+
 !Object methodsFor:'secure message sending'!
 
 ?:selector
@@ -8588,6 +8595,7 @@
     "
 ! !
 
+
 !Object methodsFor:'synchronized evaluation'!
 
 freeSynchronizationSemaphore
@@ -10346,6 +10354,9 @@
     ^ aVisitor visitObject:self with:aParameter
 ! !
 
+
+
+
 !Object class methodsFor:'documentation'!
 
 version
--- a/ObjectCoder.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/ObjectCoder.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2000 by eXept Software AG
               All Rights Reserved
@@ -82,6 +80,7 @@
     "
      Base64Coder encode:#[1 2 16rFe 16rFF]
      Base64Coder decode:'AQL+/w=='    
+     (Base64Coder decode:(Base64Coder encode:#[1 2 16rFe 16rFF])) = #[1 2 16rFe 16rFF]
     "
 !
 
@@ -204,7 +203,7 @@
 nextPut:anObject
     "encode anObject onto my stream"
 
-    self nextPut:anObject with:nil.
+    self nextPut:anObject with:nil
 !
 
 nextPut:anObject with:aParameter
@@ -274,7 +273,15 @@
 
 !ObjectCoder methodsFor:'private-accessing'!
 
+stream
+    "return my input or output stream"
+    
+    ^ stream
+!
+
 stream:aStream
+    "set my input or output stream"
+
     stream := aStream.
 ! !
 
--- a/PCFilename.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/PCFilename.st	Mon Apr 18 07:17:25 2016 +0100
@@ -168,48 +168,54 @@
     "/ instead of under any particular user.
 
     #('STX_TMPDIR' 'ST_TMPDIR' 'TMPDIR' 'TEMPDIR' 'TEMP' 'TMP' 'ALLUSERSPROFILE') do:[:envVar |
-        tempDirString := OperatingSystem getEnvironment:envVar.
-        tempDirString notNil ifTrue:[
-            "/ kludge when running cygwin: replace '/cygdrive/X/...'
-            "/ by X:\...
-            (tempDirString startsWith:'/cygdrive/') ifTrue:[
-                tempDirString := tempDirString withoutPrefix:'/cygdrive/'.
-                tempDirString size > 2 ifTrue:[
-                    (tempDirString at:2) == $/ ifTrue:[
-                        tempDirString := (tempDirString at:1) asString , ':' ,
-                                   ((tempDirString copyFrom:2) replaceAll:$/ with:$\).
-                    ].
-                ].
-            ].
-            tempDir := self named:tempDirString.    
-            (tempDir exists and:[ tempDir isWritable ]) ifTrue:[
-                ('Filename [info]: using tmp folder "%1" as specified by environment: "%2"'
-                    bindWith:tempDir pathName with:envVar) infoPrintCR.
-                ^ tempDir asFilename.
-            ].
-        ].
+	tempDirString := OperatingSystem getEnvironment:envVar.
+	tempDirString notNil ifTrue:[
+	    "/ kludge when running cygwin: replace '/cygdrive/X/...'
+	    "/ by X:\...
+	    (tempDirString startsWith:'/cygdrive/') ifTrue:[
+		tempDirString := tempDirString withoutPrefix:'/cygdrive/'.
+		tempDirString size > 2 ifTrue:[
+		    (tempDirString at:2) == $/ ifTrue:[
+			tempDirString := (tempDirString at:1) asString , ':' ,
+				   ((tempDirString copyFrom:2) replaceAll:$/ with:$\).
+		    ].
+		].
+	    ].
+	    tempDir := self named:tempDirString.
+	    (tempDir exists and:[ tempDir isWritable ]) ifTrue:[
+		('Filename [info]: using tmp folder "%1" as specified by environment: "%2"'
+		    bindWith:tempDir pathName with:envVar) infoPrintCR.
+		^ tempDir asFilename.
+	    ].
+	].
     ].
 
     winDir := OperatingSystem getWindowsDirectory asFilename.
     vol := winDir volume.
     tempDir := vol asFilename construct:'temp'.
-    (tempDir exists and:[ tempDir isWritable ]) ifFalse:[ 
-        tempDir := vol asFilename construct:'tmp'.
-        (tempDir exists and:[ tempDir isWritable ]) ifFalse:[ 
-            tempDir := winDir construct:'temp'.
-            (tempDir exists and:[ tempDir isWritable ]) ifFalse:[
-                tempDir := '.\temp' asFilename
-            ]
-        ]
+    (tempDir exists and:[ tempDir isWritable ]) ifFalse:[
+	tempDir := vol asFilename construct:'tmp'.
+	(tempDir exists and:[ tempDir isWritable ]) ifFalse:[
+	    tempDir := winDir construct:'temp'.
+	    (tempDir exists and:[ tempDir isWritable ]) ifFalse:[
+		tempDir := '.\temp' asFilename
+	    ]
+	]
     ].
     ('Filename [info]: using fallback windows tmp folder: ',tempDir pathName) infoPrintCR.
-    ^ tempDir    
+    ^ tempDir
 
     "
      Filename defaultTempDirectoryName
      Filename defaultTempDirectoryName exists
      Filename defaultTempDirectoryName isWritable
     "
+!
+
+defaultVolumeName
+    "return the default volume name."
+
+    ^ 'c:'
 ! !
 
 !PCFilename class methodsFor:'queries'!
@@ -520,7 +526,7 @@
     ^ (OperatingSystem getDriveType:pathName) == 5
 
     "
-     'd:' asFilename isCDRom   
+     'd:' asFilename isCDRom
     "
 !
 
@@ -545,14 +551,14 @@
     pathName := self asString asLowercase.
 
     "/ ((pathName = 'a:\') or:[pathName = 'b:\']) ifTrue:[^ false].
-    ^ #(2 3 5 6) includes:(OperatingSystem getDriveType:pathName) 
+    ^ #(2 3 5 6) includes:(OperatingSystem getDriveType:pathName)
 
    "
-    'z:' asFilename isDrive  
-    'c:' asFilename isDrive   
-    'd:' asFilename isDrive   
-    'a:\' asFilename isDrive   
-    'b:\' asFilename isDrive   
+    'z:' asFilename isDrive
+    'c:' asFilename isDrive
+    'd:' asFilename isDrive
+    'a:\' asFilename isDrive
+    'b:\' asFilename isDrive
    "
 !
 
@@ -925,14 +931,13 @@
 !PCFilename class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/PCFilename.st,v 1.66 2014-11-18 18:59:15 cg Exp $'
+    ^ '$Header$'
 !
 
 version_CVS
-    ^ '$Header: /cvs/stx/stx/libbasic/PCFilename.st,v 1.66 2014-11-18 18:59:15 cg Exp $'
+    ^ '$Header$'
 !
 
 version_SVN
-    ^ '$Id: PCFilename.st,v 1.66 2014-11-18 18:59:15 cg Exp $'
+    ^ '$Id$'
 ! !
-
--- a/PositionableStream.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/PositionableStream.st	Mon Apr 18 07:17:25 2016 +0100
@@ -197,6 +197,13 @@
 !PositionableStream methodsFor:'accessing'!
 
 collection
+    "return the underlying collection buffer.
+     Notice, that this buffer may become invalid after being retrieved,
+     if more data is written to the stream (because a bigger buffer might be
+     allocated). Therefore, it should be only used in special situations,
+     where an already filed buffer needs to be backpatched later
+     (eg. before being sent out to some external stream or socket)"
+    
     ^ collection
 !
 
--- a/ProjectDefinition.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/ProjectDefinition.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -2595,6 +2597,13 @@
     "Created: / 02-06-2015 / 17:41:37 / gg"
 !
 
+additional_post_nsis_rules64
+    "this will be performed after the nsis did build the program installer for 64bit build"
+    ^ ''
+
+    "Created: / 02-06-2015 / 17:41:37 / gg"
+!
+
 globalDefines
     "allow for the specification of additional defines for stc compilation of prerequisite packages
      an subprojects"
@@ -2737,7 +2746,6 @@
     "Created: / 18-08-2006 / 12:51:38 / cg"
 ! !
 
-
 !ProjectDefinition class methodsFor:'description - project information'!
 
 applicationAdditionalIconFileNames
@@ -3799,7 +3807,8 @@
         at: 'ADDITIONAL_RULES_HG' put: (self additionalRulesHG_bc_dot_mak ? '');
         at: 'ADDITIONAL_TARGETS' put: (self additionalTargets_bc_dot_mak ? '');
         at: 'ADDITIONAL_LINK_LIBRARIES' put: (self additionalLinkLibraries_bc_dot_mak ? '');
-        at: 'ADDITIONAL_POSTNSISRULES' put: (self additional_post_nsis_rules);  "/ win32 here    
+        at: 'ADDITIONAL_POSTNSISRULES' put: (self additional_post_nsis_rules);  "/ win32 bc here    
+        at: 'ADDITIONAL_POSTNSISRULES64' put: (self additional_post_nsis_rules64);  "/ win64 mingw here    
         at: 'LOCAL_INCLUDES' put: (self generateLocalIncludes_win32 ? '');
         at: 'LOCAL_DEFINES' put: self localDefines_win32 ? '';
         at: 'GLOBAL_DEFINES' put: self globalDefines_win32 ? '';
@@ -4772,7 +4781,6 @@
     ^ self subProjectMakeCallsUsing:'call vcmake %1 %2'.
 ! !
 
-
 !ProjectDefinition class methodsFor:'file templates'!
 
 autopackage_default_dot_apspec
@@ -4900,6 +4908,10 @@
 
 make.exe -N -f bc.mak  %%DEFINES%% %%*
 
+@IF "%%1" EQU "exe" exit /b 0
+@IF "%%1" EQU "setup" exit /b 0
+@IF "%%1" EQU "pluginSetup" exit /b 0
+
 %(SUBPROJECT_BMAKE_CALLS)
 '
 
@@ -4978,6 +4990,10 @@
 @REM -------
 make.exe -N -f bc.mak -DUSELCC=1 %%*
 
+@IF "%%1" EQU "exe" exit /b 0
+@IF "%%1" EQU "setup" exit /b 0
+@IF "%%1" EQU "pluginSetup" exit /b 0
+
 %(SUBPROJECT_LCCMAKE_CALLS)
 '
 
@@ -5106,6 +5122,10 @@
 @popd
 make.exe -N -f bc.mak %DEFINES% %%USEMINGW_ARG%% %%*
 
+@IF "%%1" EQU "exe" exit /b 0
+@IF "%%1" EQU "setup" exit /b 0
+@IF "%%1" EQU "pluginSetup" exit /b 0
+
 %(SUBPROJECT_MINGWMAKE_CALLS)
 '
 
@@ -5197,6 +5217,11 @@
 @REM -------
 make.exe -N -f bc.mak -DUSETCC=1 %%*
 
+@IF "%%1" EQU "exe" exit /b 0
+@IF "%%1" EQU "setup" exit /b 0
+@IF "%%1" EQU "pluginSetup" exit /b 0
+
+
 %(SUBPROJECT_TCCMAKE_CALLS)
 '
 
@@ -5226,6 +5251,9 @@
 
 make.exe -N -f bc.mak -DUSEVC=1 %DEFINES% %*
 
+@IF "%%1" EQU "exe" exit /b 0
+@IF "%%1" EQU "setup" exit /b 0
+@IF "%%1" EQU "pluginSetup" exit /b 0
 
 %(SUBPROJECT_VCMAKE_CALLS)
 '
@@ -6950,7 +6978,7 @@
 
                 "but subprojects of our prerequisites are also prerequisites"
 "/ SV: - I don't think so. Either we need them, because they have classes being superclasses
-"/ or referenced. Or we include the explicitly. In both cases we do not need thid code.
+"/ or referenced. Or we include the explicitly. In both cases we do not need this code.
 "/ But we do not want them only because there is a subProject with examples or tests!!
 
 "/                def effectiveSubProjects
@@ -6983,9 +7011,15 @@
 !
 
 allPreRequisitesSorted
-    ^ self allPreRequisitesSorted:#effectivePreRequisites
-
-    "Modified: / 25-09-2015 / 05:45:42 / Jan Vrany <jan.vrany@fit.cvut.cz>"
+    [
+        ^ self allPreRequisitesSorted:#effectivePreRequisites
+    ] on:Error do:[:ex |
+        (self confirm:(self name,' [warning]: cycle in prerequisites:' ,, Character cr, '    ', (ex parameter printStringWithSeparator:' -> ') ,, Character cr,  'Proceed with incomplete (mandatory) prerequites?'))
+        ifFalse:[
+            AbortOperationRequest raise
+        ].
+        ^ self allPreRequisitesSorted:#mandatoryPreRequisites
+    ].
 !
 
 allPreRequisitesSorted:aSelector
--- a/Smalltalk.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/Smalltalk.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -32,7 +34,7 @@
 	category:'System-Support'
 !
 
-Smalltalk comment:''
+Smalltalk comment:'documentation'
 !
 
 !Smalltalk class methodsFor:'documentation'!
@@ -2336,133 +2338,126 @@
      The package is either located in packageDirOrStringOrNil, or in the current directory (if nil).
      Answer true, if the load succeeded, false if it failed"
 
-    |packageDirOrNil "shLibName"
-     binaryClassLibraryFilename projectDefinitionFilename projectDefinitionClass projectDefinitionClassName silent somethingHasBeenLoaded
-     loadOK "exePath" errorInInitialize|
+    |packageDirOrNil binaryClassLibraryFilename projectDefinitionFilename 
+     projectDefinitionClass projectDefinitionClassName silent somethingHasBeenLoaded
+     loadOK errorInInitialize|
 
     packageDirOrStringOrNil notNil ifTrue:[
-	packageDirOrNil := packageDirOrStringOrNil asFilename.
-    ].
-    VerboseLoading ifTrue:[
-	silent := false
-    ] ifFalse:[
-	silent := (SilentLoading or:[ StandAlone ]) or:[ InfoPrinting not ].
-    ].
+        packageDirOrNil := packageDirOrStringOrNil asFilename.
+    ].
+    silent := VerboseLoading not 
+                and:[SilentLoading or:[StandAlone or:[InfoPrinting not]]].
 
     "For now: have to read the project definition first!!
      The class library may contain subclasses of classes in prerequisite packages -
-     so the prerequisite packages have to be loaded first"
-    "normally there is a project definiton, use that one to pull in the rest"
+     so the prerequisite packages have to be loaded first.
+     Normally there is a project definiton, use that one to pull in the rest"
 
     "maybe, it is already in the image"
     projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
     (projectDefinitionClass notNil and:[projectDefinitionClass supportedOnPlatform not]) ifTrue:[
-	^ PackageNotCompatibleError raiseRequestWith:aPackageString errorString:' - package is not compatible with this platform'.
+        ^ PackageNotCompatibleError raiseRequestWith:aPackageString errorString:' - package is not compatible with this platform'.
     ].
 
     "Is there a shared library (.dll or .so) ?"
     binaryClassLibraryFilename := ObjectFileLoader
-				    binaryClassFilenameForPackage:aPackageString
-				    inDirectory:packageDirOrNil.
+                                    binaryClassFilenameForPackage:aPackageString
+                                    inDirectory:packageDirOrNil.
 
     (binaryClassLibraryFilename notNil and:[binaryClassLibraryFilename exists]) ifTrue:[
-	|loadErrorOccurred|
-
-	loadErrorOccurred := false.
-	ObjectFileLoader objectFileLoadErrorNotification handle:[:ex |
-	    loadErrorOccurred := true.
-	    ex proceedWith:true.
-	] do:[
-	    loadOK := (ObjectFileLoader loadObjectFile:binaryClassLibraryFilename) notNil.
-	    "/ loadOK := self loadPackage:aPackageString fromClassLibrary:binaryClassLibraryFilename.
-	].
-	(loadOK and:[loadErrorOccurred not]) ifTrue:[
-	    silent ifFalse:[
-		Transcript showCR:('Smalltalk [info]: 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."
-	    ^ true
-	].
-
-	loadErrorOccurred ifTrue:[
-	    self breakPoint:#cg.
-	    projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
-	    projectDefinitionClass notNil ifTrue:[
-		projectDefinitionClass supportedOnPlatform ifTrue:[
-		    "/ load prerequisites...
-		    projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
-		    self breakPoint:#cg.
-		].
-	    ].
-	].
+        |loadErrorOccurred|
+
+        loadErrorOccurred := false.
+        ObjectFileLoader objectFileLoadErrorNotification handle:[:ex |
+            loadErrorOccurred := true.
+            ex proceedWith:true.
+        ] do:[
+            loadOK := (ObjectFileLoader loadObjectFile:binaryClassLibraryFilename) notNil.
+            "/ loadOK := self loadPackage:aPackageString fromClassLibrary:binaryClassLibraryFilename.
+        ].
+        (loadOK and:[loadErrorOccurred not]) ifTrue:[
+            "now, all compiled classes have been loaded.
+             keep classes in the package which are autoloaded as autoloaded."
+            ^ true
+        ].
+
+        loadErrorOccurred ifTrue:[
+            self breakPoint:#cg.
+            projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
+            projectDefinitionClass notNil ifTrue:[
+                projectDefinitionClass supportedOnPlatform ifTrue:[
+                    "/ load prerequisites...
+                    projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
+                    self breakPoint:#cg.
+                ].
+            ].
+        ].
     ].
     packageDirOrNil isNil ifTrue:[
-	^ PackageNotFoundError raiseRequestWith:aPackageString.
+        ^ PackageNotFoundError raiseRequestWith:aPackageString.
     ].
 
     "fallback - go through the project definition"
     projectDefinitionClass isNil ifTrue:[
-	projectDefinitionClassName := ProjectDefinition projectDefinitionClassNameForDefinitionOf:aPackageString.
-	"/ try to load the project definition class
-	projectDefinitionFilename := (packageDirOrNil / projectDefinitionClassName) withSuffix:'st'.
-	projectDefinitionFilename exists ifFalse:[
-	    projectDefinitionFilename := (packageDirOrNil / 'source' / projectDefinitionClassName) withSuffix:'st'.
-	].
-	projectDefinitionFilename exists ifTrue:[
-	    Class withoutUpdatingChangesDo:[
-		Smalltalk silentlyLoadingDo:[
-		    Error handle:[:ex |
-			"/ catch error during initialization;
-			ex suspendedContext withAllSendersDo:[:sender |
-			    sender selector == #initialize ifTrue:[
-				sender receiver isBehavior ifTrue:[
-				    sender receiver name = projectDefinitionClassName ifTrue:[
-					errorInInitialize := true
-				    ]
-				]
-			    ]
-			].
-			errorInInitialize ifFalse:[ ex reject ].
-		    ] do:[
-			projectDefinitionFilename fileIn.
-		    ].
-		].
-	    ].
-	    errorInInitialize ifTrue:[
-		Transcript showCR:'Smalltalk [warning]: an error happened in #initialize - retry after loading package.'.
-	    ].
-	    projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
-	].
+        projectDefinitionClassName := ProjectDefinition projectDefinitionClassNameForDefinitionOf:aPackageString.
+        "/ try to load the project definition class
+        projectDefinitionFilename := (packageDirOrNil / projectDefinitionClassName) withSuffix:'st'.
+        projectDefinitionFilename exists ifFalse:[
+            projectDefinitionFilename := (packageDirOrNil / 'source' / projectDefinitionClassName) withSuffix:'st'.
+        ].
+        projectDefinitionFilename exists ifTrue:[
+            Class withoutUpdatingChangesDo:[
+                Smalltalk silentlyLoadingDo:[
+                    Error handle:[:ex |
+                        "/ catch error during initialization;
+                        ex suspendedContext withAllSendersDo:[:sender |
+                            (sender selector == #initialize 
+                                and:[sender receiver isBehavior 
+                                and:[sender receiver name = projectDefinitionClassName]]
+                            ) ifTrue:[
+                                errorInInitialize := true
+                            ].
+                        ].
+                        errorInInitialize ifFalse:[ ex reject ].
+                    ] do:[
+                        projectDefinitionFilename fileIn.
+                    ].
+                ].
+            ].
+            errorInInitialize ifTrue:[
+                Transcript showCR:'Smalltalk [warning]: an error happened in #initialize - retry after loading package.'.
+            ].
+            projectDefinitionClass := ProjectDefinition definitionClassForPackage:aPackageString.
+        ].
     ].
     projectDefinitionClass notNil ifTrue:[
-	projectDefinitionClass autoload.
-	projectDefinitionClass supportedOnPlatform ifFalse:[
-	    ^ PackageNotCompatibleError raiseRequestWith:aPackageString errorString:' - package is not compatible with this platform'.
-	].
-	projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
-	somethingHasBeenLoaded := projectDefinitionClass loadAsAutoloaded:doLoadAsAutoloaded.
-	errorInInitialize ifTrue:[
-	    Transcript showCR:('Smalltalk [info]: retrying #initialize').
-	    projectDefinitionClass initialize.
-	].
-	(silent not and:[somethingHasBeenLoaded]) ifTrue:[
-	    Transcript showCR:('Smalltalk [info]: loaded package: ' , aPackageString , ' from project definition').
-	].
-	^ true.
+        projectDefinitionClass autoload.
+        projectDefinitionClass supportedOnPlatform ifFalse:[
+            ^ PackageNotCompatibleError raiseRequestWith:aPackageString errorString:' - package is not compatible with this platform'.
+        ].
+        projectDefinitionClass loadPreRequisitesAsAutoloaded:doLoadAsAutoloaded.
+        somethingHasBeenLoaded := projectDefinitionClass loadAsAutoloaded:doLoadAsAutoloaded.
+        errorInInitialize ifTrue:[
+            Transcript showCR:('Smalltalk [info]: retrying #initialize').
+            projectDefinitionClass initialize.
+        ].
+        (silent not and:[somethingHasBeenLoaded]) ifTrue:[
+            Transcript showCR:('Smalltalk [info]: loaded package: ' , aPackageString , ' from project definition').
+        ].
+        ^ true.
     ].
 
     "/ source files-file loading no longer supported
     "/ however, allow for autoload-stub loaded
     doLoadAsAutoloaded ifTrue:[
-	self
-	    recursiveInstallAutoloadedClassesFrom:packageDirOrNil
-	    rememberIn:(Set new)
-	    maxLevels:2
-	    noAutoload:false
-	    packageTop:packageDirOrNil
-	    showSplashInLevels:0.
-	^ true
+        self
+            recursiveInstallAutoloadedClassesFrom:packageDirOrNil
+            rememberIn:Set new
+            maxLevels:2
+            noAutoload:false
+            packageTop:packageDirOrNil
+            showSplashInLevels:0.
+        ^ true
     ].
 
     ^ PackageNotFoundError raiseRequestWith:aPackageString errorString:' - no projectDef, dll or loadAll found'.
@@ -4269,7 +4264,7 @@
 
     |idx graphicalMode arg didReadRCFile keepSplashWindow|
 
-    graphicalMode := true.
+    graphicalMode := Smalltalk isSmalltalkDevelopmentSystem.
     Initializing := true.
 
     keepSplashWindow := StartupClass perform:#keepSplashWindowOpen ifNotUnderstood:[false].
@@ -8223,13 +8218,13 @@
     (lang == #de) ifTrue:[
         proto := 'Willkommen bei %1 (%4Version %2 von %3)'. bit := 'Bit'.
     ] ifFalse:[ (lang == #fr) ifTrue:[
-        proto := 'Salut, Bienvenue à %1 (%4version %2 de %3)'
+        proto := 'Salut, Bienvenue à %1 (%4version %2 de %3)'
     ] ifFalse:[ (lang == #it) ifTrue:[
         proto := 'Ciao, benvenuto al %1 (%4versione %2 di %3)'
     ] ifFalse:[ (lang == #es) ifTrue:[
         proto := 'Hola, bienvenida a %1 (%4version %2 de %3)'
     ] ifFalse:[ (lang == #pt) ifTrue:[
-        proto := 'Ol!!, mem-vindo a %1 (%4version %2 de %3)'
+        proto := 'Olá!!, mem-vindo a %1 (%4version %2 de %3)'
     ] ifFalse:[ (lang == #no) ifTrue:[
         proto := 'Hei, verdenmottakelse til %1 (%4versjon %2 av %3)'
     ]]]]]].
--- a/StandaloneStartup.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/StandaloneStartup.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -1063,15 +1061,15 @@
 
 start
     GenericException handle:[:ex |
-        self verboseInfo:('Error during startup:').
-        self verboseInfo:(ex description).
+        self verboseInfo:'Error during startup:'.
+        self verboseInfo:ex description.
         Verbose == true ifTrue:[ex suspendedContext fullPrintAllLevels:10].
         ex reject.        
     ] do:[
         |idx|
 
-        Smalltalk showSplashMessage:('start').
-        self verboseInfo:('starting...').
+        Smalltalk showSplashMessage:'start'.
+        self verboseInfo:'starting...'.
         CommandLineArguments := (self additionalArgumentsFromRegistry) 
                                 , Smalltalk commandLineArguments.
 
@@ -1082,7 +1080,7 @@
         idx := CommandLineArguments indexOfAny:#('--newAppInstance').
         idx == 0 ifTrue:[
             self shouldReuseRunningApplication ifTrue:[
-                self verboseInfo:('should reuse app').
+                self verboseInfo:'should reuse app'.
                 "Multiple Application support:
                  if another expecco is running, ask it to open another window for me.
                  If that is the case, the following function will not return, but instead exit."
@@ -1099,7 +1097,7 @@
 
         Smalltalk isStandAloneApp ifTrue:[
             self loadPatches.
-            self verboseInfo:('setup Smalltalk').
+            self verboseInfo:'setup Smalltalk'.
         ].
         self setupSmalltalkFromArguments:CommandLineArguments.
         self main
--- a/String.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/String.st	Mon Apr 18 07:17:25 2016 +0100
@@ -514,8 +514,6 @@
 ! !
 
 
-
-
 !String class methodsFor:'queries'!
 
 defaultPlatformClass
@@ -536,9 +534,6 @@
 ! !
 
 
-
-
-
 !String methodsFor:'Compatibility-VW5.4'!
 
 asByteString
@@ -3899,6 +3894,8 @@
 !
 
 isWideString
+    "true if I require more than one byte per character"
+
     ^ false
 !
 
@@ -3991,7 +3988,6 @@
     ^ super reverse
 ! !
 
-
 !String methodsFor:'substring searching'!
 
 indexOfSubCollection:aSubString startingAt:startIndex ifAbsent:exceptionValue caseSensitive:caseSensitive
@@ -4503,7 +4499,6 @@
 
 ! !
 
-
 !String class methodsFor:'documentation'!
 
 version
--- a/TwoByteString.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/TwoByteString.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1993 by Claus Gittinger
 	      All Rights Reserved
@@ -127,7 +125,7 @@
 
     "
         'abcdef' asUnicode16String utf8Encoded
-        'abcdefäöü' asUnicode16String utf8Encoded
+        'abcdefäöü' asUnicode16String utf8Encoded
     "
 !
 
@@ -150,7 +148,7 @@
         'abcde1234' asUnicode16String utf8EncodedOn:w
      ].
      String streamContents:[:w|
-         'abcdeäöüß' asUnicode16String utf8EncodedOn:w
+         'abcdeäöüß' asUnicode16String utf8EncodedOn:w
      ].
     "
 ! !
@@ -307,16 +305,16 @@
 
     "
      'hello world' asUnicode16String characterSize
-     'hello worldüäö' asUnicode16String characterSize
+     'hello worldüäö' asUnicode16String characterSize
      'a' asUnicode16String characterSize
-     'ü' asUnicode16String characterSize
+     'ü' asUnicode16String characterSize
      'aa' asUnicode16String characterSize
-     'aü' asUnicode16String characterSize
+     'aü' asUnicode16String characterSize
      'aaa' asUnicode16String characterSize
-     'aaü' asUnicode16String characterSize
-     'aaaü' asUnicode16String characterSize
+     'aaü' asUnicode16String characterSize
+     'aaaü' asUnicode16String characterSize
      'aaaa' asUnicode16String characterSize
-     'aaaaü' asUnicode16String characterSize
+     'aaaaü' asUnicode16String characterSize
     "
 !
 
@@ -359,17 +357,19 @@
 
     "
      'hello world' asUnicode16String containsNon7BitAscii
-     'hello worldüäö' asUnicode16String containsNon7BitAscii
-     'ü' asUnicode16String containsNon7BitAscii
-     'aü' asUnicode16String containsNon7BitAscii
-     'aaü' asUnicode16String containsNon7BitAscii
-     'aaaü' asUnicode16String containsNon7BitAscii
-     'aaaaü' asUnicode16String containsNon7BitAscii
+     'hello worldüäö' asUnicode16String containsNon7BitAscii
+     'ü' asUnicode16String containsNon7BitAscii
+     'aü' asUnicode16String containsNon7BitAscii
+     'aaü' asUnicode16String containsNon7BitAscii
+     'aaaü' asUnicode16String containsNon7BitAscii
+     'aaaaü' asUnicode16String containsNon7BitAscii
      'aaaaa' asUnicode16String containsNon7BitAscii
     "
 !
 
 isWideString
+    "true if I require more than one byte per character"
+
     ^ true
 ! !
 
--- a/UserPreferences.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/UserPreferences.st	Mon Apr 18 07:17:25 2016 +0100
@@ -1828,7 +1828,7 @@
     "change the flag which enables a workaround for a redraw bug when running X/Linux in the VMWare virtual machine"
 
     self at:#enableVMWareDrawingBugWorkaround put:aBoolean.
-    (Screen notNil and:[Screen current notNil and:[Screen current platformName = #X11]]) ifTrue:[
+    (Screen notNil and:[Screen current notNil and:[Screen current platformName == #X11]]) ifTrue:[
         Screen current maxOperationsUntilFlush:(aBoolean ifTrue:[1] ifFalse:[nil])
     ].
 
--- a/Win32OperatingSystem.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/Win32OperatingSystem.st	Mon Apr 18 07:17:25 2016 +0100
@@ -902,7 +902,6 @@
     "Modified: 7.1.1997 / 19:36:11 / stefan"
 ! !
 
-
 !Win32OperatingSystem class methodsFor:'OS signal constants'!
 
 sigABRT
@@ -3765,9 +3764,26 @@
 primExec:commandPath commandLine:commandLine fileDescriptors:fdArray fork:doFork newPgrp:newPgrp inPath:dirName createFlags:flagsOrNil inheritHandles:inheritHandles
     "Internal lowLevel entry for combined fork & exec for WIN32"
 
-    |handle|
+    |handle 
+	 commandPathUni16 commandLineUni16 dirNameUni16|
 
     handle := Win32ProcessHandle new.
+	
+    commandPathUni16 := commandPath.
+    commandLineUni16 := commandLine.
+    dirNameUni16 := dirName.
+
+    commandPathUni16 notNil ifTrue:[
+        commandPathUni16 := commandPathUni16 asUnicode16String.
+    ].
+    commandLineUni16 notNil ifTrue:[
+        commandLineUni16 := commandLineUni16 asUnicode16String.
+    ].
+    dirNameUni16 notNil ifTrue:[
+        dirNameUni16 := dirNameUni16 asUnicode16String.
+    ].
+	
+	
 %{
 
     /*
@@ -3775,247 +3791,304 @@
      * otherwise, spawn a subprocess and let it execute the command.
      * Currently, only the forking version is supported (who chains anyway ?)
      */
-    char *cmdPath = 0;
-    char *cmdLine = 0;
-    char *dir = 0;
+    int i, l; // i -> for iteration, l -> for length
+
+    /* 
+     * CreateProcess supports 32767 characters/bytes including all variables and values 
+     * so take a good average for its arguments 4096
+     * ATTENTION this value is also used hardcoded in the following code to check the length
+     */
+    wchar_t cmdPathW[4096];
+    wchar_t cmdLineW[4096];
+    wchar_t dirNameW[4096];     
+
+    /* 
+     * pass pointers to CreateProcess  
+     * NULL pointers used to indicate no value
+     * so only set the pointer if the value is valid
+     */          
+    wchar_t *cmdPathWP = NULL; 
+    wchar_t *cmdLineWP = NULL; 
+    wchar_t *dirNameWP = NULL; 
+
     DWORD               fdwCreate = 0;
-    STARTUPINFO         lpsiStartInfo;
+    STARTUPINFOW        lpsiStartInfo;
     PROCESS_INFORMATION lppiProcInfo;
     SECURITY_ATTRIBUTES securityAttributes;
     SECURITY_DESCRIPTOR securityDescriptor;
 
-    if ((__isStringLike(commandPath) || (commandPath == nil)) && __isStringLike(commandLine)) {
-	HANDLE stdinHandle = NULL;
-	HANDLE stdoutHandle = NULL;
-	HANDLE stderrHandle = NULL;
-	int mustClose_stdinHandle = 0;
-	int mustClose_stdoutHandle = 0;
-	int mustClose_stderrHandle = 0;
-
-	if (commandPath != nil) {
-	    cmdPath = __stringVal(commandPath);
-	}
-	cmdLine = __stringVal(commandLine);
-
-	if (__isStringLike(dirName)) {
-	    dir = __stringVal(dirName);
-	}
-
-	/*
-	 * create descriptors as req'd
-	 */
-	memset(&securityAttributes, 0, sizeof(securityAttributes));
-	securityAttributes.nLength = sizeof(securityAttributes);
-	securityAttributes.bInheritHandle = (inheritHandles == true) ? TRUE : FALSE;
-
-	InitializeSecurityDescriptor(&securityDescriptor, SECURITY_DESCRIPTOR_REVISION);
-	SetSecurityDescriptorDacl(&securityDescriptor, -1, 0, 0);
-
-	securityAttributes.lpSecurityDescriptor = &securityDescriptor;
-	memset(&lppiProcInfo, 0, sizeof (lppiProcInfo));
-
-	memset(&lpsiStartInfo, 0, sizeof(lpsiStartInfo));
-	lpsiStartInfo.cb                = sizeof(lpsiStartInfo);
-	lpsiStartInfo.lpReserved        = NULL;
-	lpsiStartInfo.lpDesktop         = NULL;
-	lpsiStartInfo.lpTitle           = NULL;
-	lpsiStartInfo.dwX               = 0;
-	lpsiStartInfo.dwY               = 0;
-	lpsiStartInfo.dwXSize           = 100;
-	lpsiStartInfo.dwYSize           = 100;
-	lpsiStartInfo.dwXCountChars     = 0;
-	lpsiStartInfo.dwYCountChars     = 0;
-	lpsiStartInfo.dwFillAttribute   = 0;
-	lpsiStartInfo.dwFlags           = STARTF_USESHOWWINDOW | STARTF_USESTDHANDLES /*| STARTF_USEPOSITION*/;
-	lpsiStartInfo.wShowWindow       = SW_HIDE /*SW_SHOWDEFAULT*/;
-	lpsiStartInfo.cbReserved2       = 0;
-	lpsiStartInfo.lpReserved2       = NULL;
-	lpsiStartInfo.hStdInput         = NULL;
-	lpsiStartInfo.hStdOutput        = NULL;
-	lpsiStartInfo.hStdError         = NULL;
-
-	/*
-	 * set create process flags
-	 * if the flags arg is nil, use common defaults;
-	 * if non-nil, it must be a positive integer containing the fdwCreate bits.
-	 */
-	if (flagsOrNil != nil) {
-	    fdwCreate = __longIntVal(flagsOrNil);
-	} else {
-	    fdwCreate = CREATE_NEW_CONSOLE; //|IDLE_PRIORITY_CLASS; // DETACHED_PROCESS; // NORMAL_PRIORITY_CLASS ;
-	    if (newPgrp == true) {
-		fdwCreate |= CREATE_NEW_PROCESS_GROUP;
-	    }
-	    fdwCreate |= CREATE_DEFAULT_ERROR_MODE;
-	}
-
-	if (fdArray == nil) {
-	    stdinHandle  = (HANDLE) _get_osfhandle (0);
-	    stdoutHandle = (HANDLE) _get_osfhandle (1);
-	    stderrHandle  = (HANDLE) _get_osfhandle (2);
-	} else if (__isArrayLike(fdArray) && (__arraySize(fdArray) >= 3)) {
-	    if (__ArrayInstPtr(fdArray)->a_element[0] != nil) {
-		if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[0])) {
-		    stdinHandle = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[0]);
-		} else {
-		    stdinHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[0]));
-		}
-	    }
-	    if (__ArrayInstPtr(fdArray)->a_element[1] != nil) {
-		if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[1])) {
-		    stdoutHandle = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[1]);
-		} else {
-		    stdoutHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[1]));
-		}
-	    }
-	    if (__ArrayInstPtr(fdArray)->a_element[2] != nil) {
-		if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[2])) {
-		    stderrHandle  = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[2]);
-		} else {
-		    stderrHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[2]));
-		}
-	    }
-	} else {
-	    console_fprintf(stderr, "Win32OS [warning]: bad fd arg in createProcess\n");
-	}
+    if ((__isUnicode16String(commandPathUni16) || (commandPathUni16 == nil)) && __isUnicode16String(commandLineUni16)) {
+        HANDLE stdinHandle = NULL;
+        HANDLE stdoutHandle = NULL;
+        HANDLE stderrHandle = NULL;
+        int mustClose_stdinHandle = 0;
+        int mustClose_stdoutHandle = 0;
+        int mustClose_stderrHandle = 0;
+
+        /*
+         * terminate the multi byte strings
+         */
+        // #commandPathUni16
+        if (commandPathUni16 != nil) {
+            l = __unicode16StringSize(commandPathUni16);
+            if (l >= 4096) { // >= need 1 space for terminator
+                #ifdef PROCESSDEBUGWIN32
+                console_fprintf(stderr, "argument #commandPathUni16 is to long\n");
+                #endif
+                RETURN(nil);
+            }
+            for (i = 0; i < l; i++) {
+                cmdPathW[i] = __unicode16StringVal(commandPathUni16)[i];
+            }
+            cmdPathW[i] = 0; // set terminator
+            cmdPathWP = &cmdPathW[0];
+        }
+
+        // commandLineUni16
+        l = __unicode16StringSize(commandLineUni16);
+        if (l >= 4096) { // >= need 1 space for terminator
+            #ifdef PROCESSDEBUGWIN32
+            console_fprintf(stderr, "argument #commandLineUni16 is to long\n");
+            #endif
+            RETURN(nil);
+        }
+        for (i = 0; i < l; i++) {
+            cmdLineW[i] = __unicode16StringVal(commandLineUni16)[i];
+        }
+        cmdLineW[i] = 0; // set terminator
+        cmdLineWP = &cmdLineW[0];
+
+        // #dirNameUni16
+        if (__isUnicode16String(dirNameUni16)) {
+            l = __unicode16StringSize(dirNameUni16);
+            if (l >= 4096) { // >= need 1 space for terminator
+                #ifdef PROCESSDEBUGWIN32
+                console_fprintf(stderr, "argument #dirNameUni16 is to long\n");
+                #endif
+                RETURN(nil);
+            }
+            for (i = 0; i < l; i++) {
+                dirNameW[i] = __unicode16StringVal(dirNameUni16)[i];
+            }
+            dirNameW[i] = 0; // set terminator
+            dirNameWP = &dirNameW[0];
+        }
+
+        /*
+         * create descriptors as req'd
+         */
+        memset(&securityAttributes, 0, sizeof(securityAttributes));
+        securityAttributes.nLength = sizeof(securityAttributes);
+        securityAttributes.bInheritHandle = (inheritHandles == true) ? TRUE : FALSE;
+
+        InitializeSecurityDescriptor(&securityDescriptor, SECURITY_DESCRIPTOR_REVISION);
+        SetSecurityDescriptorDacl(&securityDescriptor, -1, 0, 0);
+
+        securityAttributes.lpSecurityDescriptor = &securityDescriptor;
+        memset(&lppiProcInfo, 0, sizeof (lppiProcInfo));
+
+        memset(&lpsiStartInfo, 0, sizeof(lpsiStartInfo));
+        lpsiStartInfo.cb                = sizeof(lpsiStartInfo);
+        lpsiStartInfo.lpReserved        = NULL;
+        lpsiStartInfo.lpDesktop         = NULL;
+        lpsiStartInfo.lpTitle           = NULL;
+        lpsiStartInfo.dwX               = 0;
+        lpsiStartInfo.dwY               = 0;
+        lpsiStartInfo.dwXSize           = 100;
+        lpsiStartInfo.dwYSize           = 100;
+        lpsiStartInfo.dwXCountChars     = 0;
+        lpsiStartInfo.dwYCountChars     = 0;
+        lpsiStartInfo.dwFillAttribute   = 0;
+        lpsiStartInfo.dwFlags           = STARTF_USESHOWWINDOW | STARTF_USESTDHANDLES /*| STARTF_USEPOSITION*/;
+        lpsiStartInfo.wShowWindow       = SW_HIDE /*SW_SHOWDEFAULT*/;
+        lpsiStartInfo.cbReserved2       = 0;
+        lpsiStartInfo.lpReserved2       = NULL;
+        lpsiStartInfo.hStdInput         = NULL;
+        lpsiStartInfo.hStdOutput        = NULL;
+        lpsiStartInfo.hStdError         = NULL;
+
+        /*
+         * set create process flags
+         * if the flags arg is nil, use common defaults;
+         * if non-nil, it must be a positive integer containing the fdwCreate bits.
+         */
+        if (flagsOrNil != nil) {
+            fdwCreate = __longIntVal(flagsOrNil);
+        } else {
+            fdwCreate = CREATE_NEW_CONSOLE; //|IDLE_PRIORITY_CLASS; // DETACHED_PROCESS; // NORMAL_PRIORITY_CLASS ;
+            if (newPgrp == true) {
+                fdwCreate |= CREATE_NEW_PROCESS_GROUP;
+            }
+            fdwCreate |= CREATE_DEFAULT_ERROR_MODE;
+        }
+
+        if (fdArray == nil) {
+            stdinHandle  = (HANDLE) _get_osfhandle (0);
+            stdoutHandle = (HANDLE) _get_osfhandle (1);
+            stderrHandle  = (HANDLE) _get_osfhandle (2);
+        } else if (__isArrayLike(fdArray) && (__arraySize(fdArray) >= 3)) {
+            if (__ArrayInstPtr(fdArray)->a_element[0] != nil) {
+                if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[0])) {
+                    stdinHandle = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[0]);
+                } else {
+                    stdinHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[0]));
+                }
+            }
+            if (__ArrayInstPtr(fdArray)->a_element[1] != nil) {
+                if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[1])) {
+                    stdoutHandle = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[1]);
+                } else {
+                    stdoutHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[1]));
+                }
+            }
+            if (__ArrayInstPtr(fdArray)->a_element[2] != nil) {
+                if (__isExternalAddressLike(__ArrayInstPtr(fdArray)->a_element[2])) {
+                    stderrHandle  = _HANDLEVal(__ArrayInstPtr(fdArray)->a_element[2]);
+                } else {
+                    stderrHandle = (HANDLE) _get_osfhandle (__intVal(__ArrayInstPtr(fdArray)->a_element[2]));
+                }
+            }
+        } else {
+            console_fprintf(stderr, "Win32OS [warning]: bad fd arg in createProcess\n");
+        }
 
 #if defined(PROCESSDEBUGWIN32)
-	console_fprintf(stderr, "stdin %x\n", stdinHandle);
-	console_fprintf(stderr, "stdout %x\n", stdoutHandle);
-	console_fprintf(stderr, "stderr %x\n", stderrHandle);
-#endif
-
-	{
-	    HANDLE childHandle;
-	    int sameHandle = (stdoutHandle == stderrHandle);
-
-	    // these MUST be inheritable!
-	    if (stdinHandle) {
+        console_fprintf(stderr, "stdin %x\n", stdinHandle);
+        console_fprintf(stderr, "stdout %x\n", stdoutHandle);
+        console_fprintf(stderr, "stderr %x\n", stderrHandle);
+#endif
+
+        {
+            HANDLE childHandle;
+            int sameHandle = (stdoutHandle == stderrHandle);
+
+            // these MUST be inheritable!
+            if (stdinHandle) {
 #if 0
-		if (SetHandleInformation(stdinHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
-		    // good
-		} else {
-		    console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
-		}
-#else
-		if (DuplicateHandle(GetCurrentProcess(), stdinHandle, GetCurrentProcess(),
-				      &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
-		    stdinHandle = childHandle;
-		    mustClose_stdinHandle = 1;
-		} else {
-		    console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
-		}
-#endif
-	    }
-	    if (stdoutHandle) {
+                if (SetHandleInformation(stdinHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
+                    // good
+                } else {
+                    console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
+                }
+#else
+                if (DuplicateHandle(GetCurrentProcess(), stdinHandle, GetCurrentProcess(),
+                                      &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
+                    stdinHandle = childHandle;
+                    mustClose_stdinHandle = 1;
+                } else {
+                    console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
+                }
+#endif
+            }
+            if (stdoutHandle) {
 #if 0
-		if (SetHandleInformation(stdoutHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
-		    // good
-		} else {
-		    console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
-		}
-#else
-		if (DuplicateHandle(GetCurrentProcess(), stdoutHandle, GetCurrentProcess(),
-				      &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
-		    stdoutHandle = childHandle;
-		    mustClose_stdoutHandle = 1;
-		} else {
-		    console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
-		}
-#endif
-	    }
-	    if (stderrHandle) {
-		if (sameHandle) {
-		    stderrHandle = stdoutHandle;
-		} else {
+                if (SetHandleInformation(stdoutHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
+                    // good
+                } else {
+                    console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
+                }
+#else
+                if (DuplicateHandle(GetCurrentProcess(), stdoutHandle, GetCurrentProcess(),
+                                      &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
+                    stdoutHandle = childHandle;
+                    mustClose_stdoutHandle = 1;
+                } else {
+                    console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
+                }
+#endif
+            }
+            if (stderrHandle) {
+                if (sameHandle) {
+                    stderrHandle = stdoutHandle;
+                } else {
 #if 0
-		    if (SetHandleInformation(stderrHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
-			// good
-		    } else {
-			console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
-		    }
-#else
-		    if (DuplicateHandle(GetCurrentProcess(), stderrHandle, GetCurrentProcess(),
-					  &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
-			stderrHandle = childHandle;
-			mustClose_stderrHandle = 1;
-		    } else {
-			console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
-		    }
-#endif
-		}
-	    }
-	}
-	lpsiStartInfo.hStdInput  = stdinHandle;
-	lpsiStartInfo.hStdOutput = stdoutHandle;
-	lpsiStartInfo.hStdError  = stderrHandle;
-
-	if (doFork == true) {
+                    if (SetHandleInformation(stderrHandle, HANDLE_FLAG_INHERIT, HANDLE_FLAG_INHERIT)) {
+                        // good
+                    } else {
+                        console_fprintf(stderr, "Win32OS [warning]: SetHandleInformation failed in createProcess\n");
+                    }
+#else
+                    if (DuplicateHandle(GetCurrentProcess(), stderrHandle, GetCurrentProcess(),
+                                          &childHandle, 0, TRUE, DUPLICATE_SAME_ACCESS)) {
+                        stderrHandle = childHandle;
+                        mustClose_stderrHandle = 1;
+                    } else {
+                        console_fprintf(stderr, "Win32OS [warning]: duplicateHandle failed in createProcess\n");
+                    }
+#endif
+                }
+            }
+        }
+        lpsiStartInfo.hStdInput  = stdinHandle;
+        lpsiStartInfo.hStdOutput = stdoutHandle;
+        lpsiStartInfo.hStdError  = stderrHandle;
+
+        if (doFork == true) {
 #ifdef PROCESSDEBUGWIN32
-	    console_fprintf(stderr, "create process cmdPath:<%s> cmdLine:<%s> in <%s>\n", cmdPath, cmdLine, dir);
-#endif
-	    if (CreateProcessA( cmdPath,
-				cmdLine,
-				&securityAttributes, NULL /* &securityAttributes */,
-				securityAttributes.bInheritHandle,      /* inherit handles */
-				fdwCreate | CREATE_SUSPENDED,           /* resume after setting affinity */
-				NULL,                                   /* env */
-				dir,
-				&lpsiStartInfo,
-				&lppiProcInfo ))
-	    {
-		DWORD_PTR processAffinityMask, systemAffinityMask;
-
-		/*
-		 * Process was created suspended, now set the affinity mask
-		 * to any processor, and resume the processes main thread.
-		 * (librun/process.s limited the affinity to a single processor).
-		 */
-		GetProcessAffinityMask(lppiProcInfo.hProcess, &processAffinityMask, &systemAffinityMask);
-		SetProcessAffinityMask(lppiProcInfo.hProcess, systemAffinityMask);
-		if ((fdwCreate & CREATE_SUSPENDED) == 0) {
-		    ResumeThread(lppiProcInfo.hThread);
-		}
-		CloseHandle(lppiProcInfo.hThread);
+            console_fprintf(stderr, "create process cmdPath:<%s> cmdLine:<%s> in <%s>\n", cmdPath, cmdLine, dir);
+#endif
+            if (CreateProcessW( cmdPathWP,
+                                cmdLineWP,
+                                &securityAttributes, NULL /* &securityAttributes */,
+                                securityAttributes.bInheritHandle,      /* inherit handles */
+                                fdwCreate | CREATE_SUSPENDED,           /* resume after setting affinity */
+                                NULL,                                   /* env */
+                                dirNameWP,
+                                &lpsiStartInfo,
+                                &lppiProcInfo ))
+            {
+                DWORD_PTR processAffinityMask, systemAffinityMask;
+
+                /*
+                 * Process was created suspended, now set the affinity mask
+                 * to any processor, and resume the processes main thread.
+                 * (librun/process.s limited the affinity to a single processor).
+                 */
+                GetProcessAffinityMask(lppiProcInfo.hProcess, &processAffinityMask, &systemAffinityMask);
+                SetProcessAffinityMask(lppiProcInfo.hProcess, systemAffinityMask);
+                if ((fdwCreate & CREATE_SUSPENDED) == 0) {
+                    ResumeThread(lppiProcInfo.hThread);
+                }
+                CloseHandle(lppiProcInfo.hThread);
 
 #if 0
-		// only works with real console handles
-		{
-		    // change the child's stdIn (console) mode
-		    DWORD mode = 0;
-
-		    if (! GetConsoleMode(stdinHandle, &mode)) {
-			console_fprintf(stderr, "Win32OS [warning]: GetConsoleMode failed in createProcess\n");
-		    }
-		    if (! SetConsoleMode(stdinHandle, mode & (~ENABLE_ECHO_INPUT))){
-			console_fprintf(stderr, "Win32OS [warning]: SetConsoleMode failed in createProcess\n");
-		    }
-		}
-#endif
-		if (mustClose_stdinHandle) {
-		    CloseHandle(stdinHandle);
-		}
-		if (mustClose_stdoutHandle) {
-		    CloseHandle(stdoutHandle);
-		}
-		if (mustClose_stderrHandle) {
-		    CloseHandle(stderrHandle);
-		}
+                // only works with real console handles
+                {
+                    // change the child's stdIn (console) mode
+                    DWORD mode = 0;
+
+                    if (! GetConsoleMode(stdinHandle, &mode)) {
+                        console_fprintf(stderr, "Win32OS [warning]: GetConsoleMode failed in createProcess\n");
+                    }
+                    if (! SetConsoleMode(stdinHandle, mode & (~ENABLE_ECHO_INPUT))){
+                        console_fprintf(stderr, "Win32OS [warning]: SetConsoleMode failed in createProcess\n");
+                    }
+                }
+#endif
+                if (mustClose_stdinHandle) {
+                    CloseHandle(stdinHandle);
+                }
+                if (mustClose_stdoutHandle) {
+                    CloseHandle(stdoutHandle);
+                }
+                if (mustClose_stderrHandle) {
+                    CloseHandle(stderrHandle);
+                }
 #ifdef PROCESSDEBUGWIN32
-		console_fprintf(stderr, "created process hProcess=%x\n", lppiProcInfo.hProcess);
-#endif
-
-		__externalAddressVal(handle) = lppiProcInfo.hProcess;
-		((struct __Win32OperatingSystem__Win32ProcessHandle_struct *)(handle))->pid = __mkSmallInteger(lppiProcInfo.dwProcessId);
-		RETURN (handle);
-	    }
+                console_fprintf(stderr, "created process hProcess=%x\n", lppiProcInfo.hProcess);
+#endif
+
+                __externalAddressVal(handle) = lppiProcInfo.hProcess;
+                ((struct __Win32OperatingSystem__Win32ProcessHandle_struct *)(handle))->pid = __mkSmallInteger(lppiProcInfo.dwProcessId);
+                RETURN (handle);
+            }
 #ifdef PROCESSDEBUGWIN32
-	    console_fprintf(stderr, "created process error %d\n", GetLastError());
-#endif
-	    RETURN (nil);
-	} else {
-	    ; /* should never be called that way */
-	}
+            console_fprintf(stderr, "created process error %d\n", GetLastError());
+#endif
+            RETURN (nil);
+        } else {
+            ; /* should never be called that way */
+        }
     }
 %}.
     "
--- a/stx_libbasic.st	Thu Apr 14 08:02:44 2016 +0100
+++ b/stx_libbasic.st	Mon Apr 18 07:17:25 2016 +0100
@@ -385,7 +385,7 @@
         SameForAllNotification
         SemaphoreSet
         SignalSet
-        SimpleExternalLibraryFunction
+        (SimpleExternalLibraryFunction autoload)
         SnapshotError
         SortedCollection
         StringCollection