Merge jv
authorJan Vrany <jan.vrany@fit.cvut.cz>
Fri, 08 Apr 2016 07:02:36 +0100
branchjv
changeset 19559 d35a89d5c0ec
parent 19533 1c9224a6ec00 (current diff)
parent 19558 2636649cfaab (diff)
child 19567 33f60845c4bc
Merge
ApplicationDefinition.st
Character.st
Date.st
Dictionary.st
ExternalLibraryFunction.st
ExternalStructure.st
IdentityDictionary.st
IdentitySet.st
Integer.st
LargeInteger.st
Object.st
ProjectDefinition.st
SequenceableCollection.st
Set.st
UninterpretedBytes.st
WeakArray.st
WeakValueDictionary.st
WeakValueIdentityDictionary.st
stx_libbasic.st
--- a/ApplicationDefinition.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/ApplicationDefinition.st	Fri Apr 08 07:02:36 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 2006 by eXept Software AG
               All Rights Reserved
@@ -917,6 +919,7 @@
         at: 'NOCONSOLE_APPLICATION_OR_EMPTY' put:(self makeNonConsoleApplication ifTrue:['noConsoleApp'] ifFalse:'');
         at: 'APPLICATION' put: (self applicationName);
         at: 'NSI_FILENAME' put: self nsiFilename ;
+        at: 'PRODUCT_NAME' put: (self productName);
         at: 'CONSOLE_APPLICATION' put: (self applicationNameConsole);
         at: 'NOCONSOLE_APPLICATION' put: (self applicationNameNoConsole);
         at: 'NOCONSOLE_LOGFILE' put:(self logFilenameNoConsole);
@@ -1731,6 +1734,19 @@
 #  this has changed; it is now also possible to build using microsoft visual c
 #    (called via vcmake, by "make.exe -f bc.mak -DUSEVC")
 #
+# Rules found here:
+#   bmake 
+#       - build everything, incl. a self installing exe for deployment
+#   bmake exe
+#       - only build the executable; to be executed and tested here
+#   bmake setup
+#       - make the self installing exe (assuming that the exe is already present)
+#   bmake clean
+#       - remove everything that is not needed to execute
+#   bmake clobber
+#       - remove everything that cannot be reconstructed by bmake
+#
+# For a 64bit build, replace bmake by mingwmake.
 
 TOP=%(TOP)       
 INCLUDE_TOP=$(TOP)\..
@@ -1839,10 +1855,21 @@
 
 # a nullsoft installable delivery
 # This uses the Nullsoft Installer Package and works in Windows only
+
+!!if defined(USEMINGW64)
+
+setup: $(PROJECT) postBuildCleanup %(NSI_FILENAME) 
+        $(MAKENSIS) /DOBJ_DIR=objmingw /DSETUP_NAME=%(PRODUCT_NAME)Setup64 %(NSI_FILENAME)
+        %(ADDITIONAL_POSTNSISRULES)
+
+!!else
+
 setup: $(PROJECT) postBuildCleanup %(NSI_FILENAME)
-        $(MAKENSIS) %(NSI_FILENAME)
+        $(MAKENSIS) /DOBJ_DIR=objmingw /DSETUP_NAME=%(PRODUCT_NAME)Setup %(NSI_FILENAME)
         %(ADDITIONAL_POSTNSISRULES)
 
+!!endif
+
 newBuildDate:
         del buildDate.h
 
@@ -2720,6 +2747,13 @@
 !!define PRODUCT_UNINST_KEY "Software\Microsoft\Windows\CurrentVersion\Uninstall\${PRODUCT_FILENAME}"
 !!define PRODUCT_UNINST_ROOT_KEY "HKLM"
 
+;
+; SETUP_NAME can come from makefile as either setup or setup64
+;
+!!if "${SETUP_NAME}" == ""
+SETUP_NAME="%(PRODUCT_NAME)Setup"
+!!endif
+
 !!define STX_ROOT "%(TOP)\.."
 
 SetCompressor /solid lzma
@@ -2783,7 +2817,7 @@
 VIAddVersionKey /LANG=${LANG_ENGLISH} "LegalCopyright" "%(LEGAL_COPYRIGHT)"
 
 
-OutFile "%(PRODUCT_FILENAME)Setup.exe"
+OutFile "${SETUP_NAME}.exe"
 InstallDir "%(PRODUCT_INSTALLDIR)"
 ShowInstDetails show
 ShowUnInstDetails show
@@ -2858,7 +2892,7 @@
   WriteRegStr ${PRODUCT_UNINST_ROOT_KEY} "${PRODUCT_UNINST_KEY}" "Publisher" "${PRODUCT_PUBLISHER}"
 SectionEnd
 
-LangString appOpen ${LANG_GERMAN}  "Mit %(PRODUCT_NAME) ffnen"
+LangString appOpen ${LANG_GERMAN}  "Mit %(PRODUCT_NAME) öffnen"
 LangString appOpen ${LANG_ENGLISH} "Open with %(PRODUCT_NAME)"
 
 LangString DESC_Section1 ${LANG_ENGLISH} "Program components of %(PRODUCT_NAME)"
@@ -2892,7 +2926,7 @@
 
 Function un.onInit
 !!insertmacro MUI_UNGETLANGUAGE
-  MessageBox MB_ICONQUESTION|MB_YESNO|MB_DEFBUTTON2 "Mchten Sie %(PRODUCT_NAME) und alle seine Komponenten deinstallieren?" IDYES +2
+  MessageBox MB_ICONQUESTION|MB_YESNO|MB_DEFBUTTON2 "Möchten Sie %(PRODUCT_NAME) und alle seine Komponenten deinstallieren?" IDYES +2
   Abort
 FunctionEnd
 
--- a/Character.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/Character.st	Fri Apr 08 07:02:36 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -1489,7 +1491,7 @@
     |s|
 
     asciivalue <= 16r7F ifTrue:[
-	^ self asString.
+        ^ self asString.
     ].
 
     s := WriteStream on:(String new:6).
@@ -1497,7 +1499,8 @@
     ^ s contents
 
     "
-	'ä' utf8Encoded
+     'ä' utf8Encoded 
+     'a' utf8Encoded 
     "
 ! !
 
@@ -2565,9 +2568,9 @@
 
     "
      $e asNonDiacritical
-     $é asNonDiacritical
-     $ä asNonDiacritical
-     $å asNonDiacritical
+     $é asNonDiacritical
+     $ä asNonDiacritical
+     $Ã¥ asNonDiacritical
     "
 !
 
--- a/Date.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/Date.st	Fri Apr 08 07:02:36 2016 +0100
@@ -95,8 +95,7 @@
 initDefaultNames
     "read the language specific names."
 
-    |enDayNames enDayAbbrevs enMonthNames enMonthAbbrevs
-     enDefaultFormat enLongFormat enShortFormat |
+    |enDayNames enDayAbbrevs enMonthNames enMonthAbbrevs|
 
     DayNames := Dictionary new.
     DayAbbrevs := Dictionary new.
@@ -153,9 +152,9 @@
     MonthNames at:#'en' put:enMonthNames.
     MonthAbbrevs at:#'en' put:enMonthAbbrevs.
 
-    DefaultFormats at:#'en' put:(enDefaultFormat := '%d-%m-%y').
-    ShortFormats at:#'en' put:(enShortFormat := '%d-%m-%y').
-    LongFormats at:#'en' put:(enLongFormat := '%(dayName), %d-%m-%y').
+    DefaultFormats at:#'en' put:('%d-%m-%y').
+    ShortFormats at:#'en' put:('%d-%m-%y').
+    LongFormats at:#'en' put:('%(dayName), %d-%m-%y').
 
     "/ take the "master" language here, for the caching
     EnvironmentChange := (Smalltalk language asSymbol ~~ #'en').
@@ -1897,6 +1896,7 @@
     "Modified: 8.10.1996 / 19:25:39 / cg"
 ! !
 
+
 !Date class methodsFor:'private'!
 
 dayAbbrevsForLanguage:languageOrNilForDefault
@@ -2113,6 +2113,7 @@
     "
 ! !
 
+
 !Date methodsFor:'Compatibility-ANSI'!
 
 dayOfWeek
@@ -3270,6 +3271,7 @@
 ! !
 
 
+
 !Date methodsFor:'obsolete'!
 
 asAbsoluteTime
@@ -3340,6 +3342,7 @@
     ^ self addDays:days
 ! !
 
+
 !Date methodsFor:'printing & storing'!
 
 addPrintBindingsTo:aDictionary
--- a/Dictionary.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/Dictionary.st	Fri Apr 08 07:02:36 2016 +0100
@@ -292,6 +292,8 @@
     ^ true
 ! !
 
+
+
 !Dictionary methodsFor:'accessing'!
 
 associationAt:aKey
@@ -416,7 +418,7 @@
               Iterate over a copy to do this."
 
     |index "{ Class: SmallInteger }"
-     k newValue|
+     k newValue oldKeyArray|
 
     (k := aKey) isNil ifTrue:[
         k := NilEntry
@@ -428,11 +430,20 @@
         ^ valueArray at:index.
     ].
     "/ a new one
+    oldKeyArray := keyArray.
     newValue := valueBlock value.
-    keyArray basicAt:index put:k.
-    valueArray basicAt:index put:newValue.
-    tally := tally + 1.
-    self possiblyGrow.
+
+    (keyArray == oldKeyArray and:[(keyArray basicAt:index) isNil]) ifTrue:[
+        "I haven't been changed while executing valueBlock. Do it fast..."
+        keyArray basicAt:index put:k.
+        valueArray basicAt:index put:newValue.
+        tally := tally + 1.
+        self possiblyGrow.
+    ] ifFalse:[
+        "I have been changed while performing the valueBlock"
+"/        self at:k put:newValue.
+        self error:'Dictionary: inconsistency while performing #at:ifAbsentPut:'.
+    ].
     ^ newValue
 
     "
@@ -2329,6 +2340,7 @@
     ^ aVisitor visitDictionary:self with:aParameter
 ! !
 
+
 !Dictionary class methodsFor:'documentation'!
 
 version
--- a/ExternalLibraryFunction.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/ExternalLibraryFunction.st	Fri Apr 08 07:02:36 2016 +0100
@@ -66,6 +66,12 @@
    extern ffi_type *__get_ffi_type_double();
    extern ffi_type *__get_ffi_type_void();
    extern ffi_type *__get_ffi_type_pointer();
+   extern INTFUNC __get_ffi_prep_cif();
+   extern INTFUNC __get_ffi_call();
+#  ifdef _MINGW__
+#   define ffi_prep_cif (*(__get_ffi_prep_cif()))
+#   define ffi_call (*(__get_ffi_call()))
+#  endif
 # endif
 
 #endif
@@ -94,32 +100,33 @@
     instances of me are used to interface to external library functions (as found in a dll/shared object).
 
     Inside a method, when a special external-call pragma such as:
-	<api: bool MessageBeep(uint)>
+        <api: bool MessageBeep(uint)>
 
     is encountered by the parser, the compiler generates a call via
-	<correspondingExternalLibraryFunctionObject> invokeWithArguments: argumentArray.
+        <correspondingExternalLibraryFunctionObject> invokeWithArguments: argumentArray.
+    and the correspondingExternalLibraryFunctionObject is kept in the literal array.
 
     In the invoke method, the library is checked to be loaded (and loaded if not already),
     the arguments are converted to C and pushed onto the C-stack, the function is called,
     and finally, the return value is converted back from C to a smalltalk object.
 
     The parser supports the call-syntax of various other smalltalk dialects:
-	Squeak / ST-X:
-	    <cdecl:   [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >
-	    <apicall: [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >
+        Squeak / ST-X:
+            <cdecl:   [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >
+            <apicall: [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >
 
-	Dolphin:
-	    <stdcall: [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>
-	    <cdecl:   [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>
+        Dolphin:
+            <stdcall: [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>
+            <cdecl:   [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>
 
-	ST/V:
-	    <api: functionName argType1 .. argTypeN returnType>
-	    <ccall: functionName argType1 .. argTypeN returnType>
-	    <ole: vFunctionIndex argType1 .. argTypeN returnType>
+        ST/V:
+            <api: functionName argType1 .. argTypeN returnType>
+            <ccall: functionName argType1 .. argTypeN returnType>
+            <ole: vFunctionIndex argType1 .. argTypeN returnType>
 
-	VisualWorks:
-	    <c: ...>
-	    <c: #define NAME value>
+        VisualWorks:
+            <c: ...>
+            <c: #define NAME value>
 "
 !
 
@@ -203,24 +210,28 @@
 
     oldPath := self dllPath.
     (oldPath includes:aDirectoryPathName) ifFalse:[
-        newPath := oldPath asOrderedCollection.
-        newPath add:aDirectoryPathName.
-        self dllPath:newPath
+	newPath := oldPath asOrderedCollection.
+	newPath add:aDirectoryPathName.
+	self dllPath:newPath
     ]
 !
 
 dllMapping
     "allows for dll's to be replaced,
      for example, if you want to use the mozilla sqlite dll
-	C:\Program Files\Mozilla Firefox\mozsqlite3.dll
+        C:\Program Files\Mozilla Firefox\mozsqlite3.dll
      for the sqlite3, execute:
-	ExternalLibraryFunction
-	    dllMapping at:'sqlite3'
-	    put: 'C:\Program Files\Mozilla Firefox\mozsqlite3.dll'
+        ExternalLibraryFunction
+            dllMapping at:'sqlite3'
+            put: 'C:\Program Files\Mozilla Firefox\mozsqlite3.dll'
+     for mingw:
+        ExternalLibraryFunction
+            dllMapping at:'sqlite3'
+            put:'C:\mingw64\opt\bin\libsqlite3-0.dll'
     "
 
     DllMapping isNil ifTrue:[
-	DllMapping := Dictionary new.
+        DllMapping := Dictionary new.
     ].
     ^ DllMapping
 
@@ -228,10 +239,14 @@
 !
 
 dllPath
+    "provide a default dllPath, where external libraries are searched for"
+
     ^ DLLPATH
 !
 
 dllPath:aCollectionOfDirectoryPathNames
+    "provide a default dllPath, where external libraries are searched for"
+
     DLLPATH := aCollectionOfDirectoryPathNames
 !
 
@@ -334,9 +349,9 @@
 
 ffiTypeSymbolForType:aType
     "map type to one of the ffi-supported ones:
-        sint8, sint16, sint32, sint64
-        uint8, uint16, uint32, uint64
-        bool void pointer handle
+	sint8, sint16, sint32, sint64
+	uint8, uint16, uint32, uint64
+	bool void pointer handle
     "
 
     aType == #sint8           ifTrue:[^ aType ].
@@ -405,24 +420,24 @@
     aType == #BYTE            ifTrue:[^ #uint8 ].
     aType == #DWORD           ifTrue:[^ #uint32 ].
     aType == #HANDLE          ifTrue:[^ #pointer ].
-    aType == #HRESULT         ifTrue:[^ #hresult ]. 
+    aType == #HRESULT         ifTrue:[^ #hresult ].
 
     "/ care for 64bit machines
     aType == #SIZE_T          ifTrue:[^ ExternalAddress pointerSize == 8 ifTrue:[#uint64] ifFalse:[#uint32]].
     aType == #BSTR            ifTrue:[^ #wcharPointer].
 
     (aType isString or:[aType isSymbol]) ifFalse:[
-        CType isNil ifTrue:[
-            self error:'unknown type'.
-        ].
-        ^ aType typeSymbol.
+	CType isNil ifTrue:[
+	    self error:'unknown type'.
+	].
+	^ aType typeSymbol.
     ].
 
     (aType endsWith:'*') ifTrue:[
-        ^ #pointer.
+	^ #pointer.
     ].
     (aType endsWith:'Pointer') ifTrue:[
-        ^ #pointer.
+	^ #pointer.
     ].
     ^ aType
 
@@ -769,7 +784,7 @@
      Also, this deals with pointer size differences."
 
     argumentTypes notEmptyOrNil ifTrue:[
-        argumentTypes := argumentTypes collect:[:argType | self class ffiTypeSymbolForType:argType].
+	argumentTypes := argumentTypes collect:[:argType | self class ffiTypeSymbolForType:argType].
     ].
     returnType := self class ffiTypeSymbolForType:returnType.
 
@@ -783,43 +798,43 @@
     |handle moduleNameUsed functionName|
 
     name isNumber ifTrue:[
-        self isCPPFunction ifTrue:[
-            "/ no need to load a dll.
-            ^ self
-        ]
+	self isCPPFunction ifTrue:[
+	    "/ no need to load a dll.
+	    ^ self
+	]
     ].
 
     "/ in some other smalltalks, there is no moduleName in the ffi-spec;
     "/ instead, the class provides the libraryName...
     (moduleNameUsed := moduleName) isNil ifTrue:[
-        owningClass isNil ifTrue:[
-            self error:'Missing moduleName'.
-        ].
-        moduleNameUsed := owningClass theNonMetaclass libraryName asSymbol.
+	owningClass isNil ifTrue:[
+	    self error:'Missing moduleName'.
+	].
+	moduleNameUsed := owningClass theNonMetaclass libraryName asSymbol.
     ].
     moduleHandle isNil ifTrue:[
-        "/ speedup. in 95% of all calls, the same moduleName is resolved here
-        (LastModuleHandleHolder isNil
-        or:[ (handle := LastModuleHandleHolder at:1) isNil
-        or:[ LastModuleHandleName ~= moduleNameUsed ]]) ifTrue:[
+	"/ speedup. in 95% of all calls, the same moduleName is resolved here
+	(LastModuleHandleHolder isNil
+	or:[ (handle := LastModuleHandleHolder at:1) isNil
+	or:[ LastModuleHandleName ~= moduleNameUsed ]]) ifTrue:[
 
-            handle := self loadLibrary:moduleNameUsed.
-            handle isNil ifTrue:[
-                self error:('Cannot find or load dll/module: "%1"' bindWith: moduleNameUsed).
-            ].
-            LastModuleHandleHolder := WeakArray with:handle.
-            LastModuleHandleName := moduleNameUsed.
-        ].
-        moduleHandle := handle.
+	    handle := self loadLibrary:moduleNameUsed.
+	    handle isNil ifTrue:[
+		self error:('Cannot find or load dll/module: "%1"' bindWith: moduleNameUsed).
+	    ].
+	    LastModuleHandleHolder := WeakArray with:handle.
+	    LastModuleHandleName := moduleNameUsed.
+	].
+	moduleHandle := handle.
     ].
     name isNumber ifFalse:[
-        functionName := name.
-        (moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
-            (moduleHandle getFunctionAddress:('_', functionName) into:self) isNil ifTrue:[
-                moduleHandle := nil.
-                self error:'Missing function: ', name, ' in module: ', moduleNameUsed.
-            ].
-        ].
+	functionName := name.
+	(moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
+	    (moduleHandle getFunctionAddress:('_', functionName) into:self) isNil ifTrue:[
+		moduleHandle := nil.
+		self error:'Missing function: ', name, ' in module: ', moduleNameUsed.
+	    ].
+	].
     ].
 
     "Modified: / 10-04-2012 / 12:12:44 / cg"
@@ -835,7 +850,7 @@
 
     filename := dllName.
     DllMapping notNil ifTrue:[
-        filename := DllMapping at:filename ifAbsent:[ filename ]
+	filename := DllMapping at:filename ifAbsent:[ filename ]
     ].
 
     filename := filename asFilename.
@@ -846,25 +861,25 @@
     handle notNil ifTrue:[^ handle ].
 
     filename isAbsolute ifFalse:[
-        "First ask the class defining the ExternalFunction for the location of the dlls ..."
-        owningClass notNil ifTrue:[
-            owningClass dllPath do:[:eachDirectory |
-                handle := ObjectFileLoader
-                            loadDynamicObject:(eachDirectory asFilename construct:nameString) pathName.
-                handle notNil ifTrue:[^ handle ].
-            ].
-        ].
-        ".. then ask the system"
-        self class dllPath do:[:eachDirectory |
-            handle := ObjectFileLoader
-                        loadDynamicObject:(eachDirectory asFilename construct:nameString) pathName.
-            handle notNil ifTrue:[^ handle ].
-        ].
+	"First ask the class defining the ExternalFunction for the location of the dlls ..."
+	owningClass notNil ifTrue:[
+	    owningClass dllPath do:[:eachDirectory |
+		handle := ObjectFileLoader
+			    loadDynamicObject:(eachDirectory asFilename construct:nameString) pathName.
+		handle notNil ifTrue:[^ handle ].
+	    ].
+	].
+	".. then ask the system"
+	self class dllPath do:[:eachDirectory |
+	    handle := ObjectFileLoader
+			loadDynamicObject:(eachDirectory asFilename construct:nameString) pathName.
+	    handle notNil ifTrue:[^ handle ].
+	].
     ].
 
     filename suffix isEmpty ifTrue:[
-        "/ try again with the OS-specific dll-extension
-        ^ self loadLibrary:(filename withSuffix:ObjectFileLoader sharedLibrarySuffix)
+	"/ try again with the OS-specific dll-extension
+	^ self loadLibrary:(filename withSuffix:ObjectFileLoader sharedLibrarySuffix)
     ].
 
     ^ nil
@@ -874,12 +889,12 @@
 
 prepareInvoke
     "called before invoked.
-     When called the very first time, moduleHandle is nil, 
+     When called the very first time, moduleHandle is nil,
      and we ensure that the dll is loaded, the function address is extracted"
 
     (moduleHandle isNil or:[self hasCode not]) ifTrue:[
-        self linkToModule.
-        self adjustTypes.
+	self linkToModule.
+	self adjustTypes.
     ].
 ! !
 
@@ -955,36 +970,36 @@
     virtual := self isVirtualCPP.
     objectiveC := self isObjectiveC.
     (virtual "or:[self isNonVirtualCPP]") ifTrue:[
-        aReceiverOrNil isNil ifTrue:[
-            "/ must have a c++ object instance
-            self primitiveFailed.
-        ].
+	aReceiverOrNil isNil ifTrue:[
+	    "/ must have a c++ object instance
+	    self primitiveFailed.
+	].
 
-        "/ and it must be a kind of ExternalStructure !!
-        (aReceiverOrNil isKindOf:ExternalStructure) ifFalse:[
-            self primitiveFailed.
-        ].
-        virtual ifTrue:[
-            vtOffset := name.
-            (vtOffset between:0 and:10000) ifFalse:[
-                self primitiveFailed.
-            ]
-        ].
+	"/ and it must be a kind of ExternalStructure !!
+	(aReceiverOrNil isKindOf:ExternalStructure) ifFalse:[
+	    self primitiveFailed.
+	].
+	virtual ifTrue:[
+	    vtOffset := name.
+	    (vtOffset between:0 and:10000) ifFalse:[
+		self primitiveFailed.
+	    ]
+	].
     ] ifFalse:[
-        objectiveC ifTrue:[
-            aReceiverOrNil isNil ifTrue:[
-                "/ must have an objective-c object instance
-                self primitiveFailed.
-            ].
-            (aReceiverOrNil isObjectiveCObject) ifFalse:[
-                self primitiveFailed
-            ]
-        ] ifFalse:[
-            aReceiverOrNil notNil ifTrue:[
-                "/ must NOT have a c++/objectiveC object instance
-                self primitiveFailed.
-            ]
-        ].
+	objectiveC ifTrue:[
+	    aReceiverOrNil isNil ifTrue:[
+		"/ must have an objective-c object instance
+		self primitiveFailed.
+	    ].
+	    (aReceiverOrNil isObjectiveCObject) ifFalse:[
+		self primitiveFailed
+	    ]
+	] ifFalse:[
+	    aReceiverOrNil notNil ifTrue:[
+		"/ must NOT have a c++/objectiveC object instance
+		self primitiveFailed.
+	    ]
+	].
     ].
     async := self isAsync.
     unlimitedStack := self isUnlimitedStack.
@@ -1013,14 +1028,14 @@
     ffi_type *__returnType = NULL;
 
     union u {
-        INT iVal;
-        float fVal;
-        double dVal;
-        void *pointerVal;
+	INT iVal;
+	float fVal;
+	double dVal;
+	void *pointerVal;
 # if 0 && defined(HAS_LONGLONG)
-        long long longLongVal;
+	long long longLongVal;
 # else
-        __int64__ longLongVal;
+	__int64__ longLongVal;
 # endif
     };
     union u __argValuesIncludingThis[MAX_ARGS+1];
@@ -1038,29 +1053,29 @@
 
 #   define __FAIL__(fcode) \
     { \
-        failureCode = fcode; failureArgNr = __mkSmallInteger(i+1); goto getOutOfHere; \
+	failureCode = fcode; failureArgNr = __mkSmallInteger(i+1); goto getOutOfHere; \
     }
 
     if (argumentsOrNil == nil) {
-        __numArgs = 0;
+	__numArgs = 0;
     } else if (__isArray(argumentsOrNil)) {
-        __numArgs = __arraySize(argumentsOrNil);
+	__numArgs = __arraySize(argumentsOrNil);
     } else {
-        __FAIL__(@symbol(BadArgumentVector))
+	__FAIL__(@symbol(BadArgumentVector))
     }
     if (argTypeSymbols == nil) {
-        __numArgsWanted = 0;
+	__numArgsWanted = 0;
     } else if (__isArray(argTypeSymbols)) {
-        __numArgsWanted = __arraySize(argTypeSymbols);
+	__numArgsWanted = __arraySize(argTypeSymbols);
     } else {
-        __FAIL__(@symbol(BadArgumentTypeVector))
+	__FAIL__(@symbol(BadArgumentTypeVector))
     }
 
     if (__numArgs != __numArgsWanted) {
-        __FAIL__(@symbol(ArgumentCountMismatch))
+	__FAIL__(@symbol(ArgumentCountMismatch))
     }
     if (__numArgs > MAX_ARGS) {
-        __FAIL__(@symbol(TooManyArguments))
+	__FAIL__(@symbol(TooManyArguments))
     }
 
     /*
@@ -1069,136 +1084,136 @@
     __returnValuePointer = &__returnValue;
 
     if (returnTypeSymbol == @symbol(voidPointer)) {
-        returnTypeSymbol = @symbol(handle);
+	returnTypeSymbol = @symbol(handle);
     } else if (returnTypeSymbol == @symbol(hresult)) {
-        returnTypeSymbol = @symbol(uint32);
+	returnTypeSymbol = @symbol(uint32);
     }
 
     if (returnTypeSymbol == @symbol(int)) {
-        __returnType = __get_ffi_type_sint();
+	__returnType = __get_ffi_type_sint();
     } else if (returnTypeSymbol == @symbol(uint)) {
-        __returnType = __get_ffi_type_uint();
+	__returnType = __get_ffi_type_uint();
     } else if (returnTypeSymbol == @symbol(uint8)) {
-        __returnType = __get_ffi_type_uint8();
+	__returnType = __get_ffi_type_uint8();
     } else if (returnTypeSymbol == @symbol(uint16)) {
-        __returnType = __get_ffi_type_uint16();
+	__returnType = __get_ffi_type_uint16();
     } else if (returnTypeSymbol == @symbol(uint32)) {
-        __returnType = __get_ffi_type_uint32();
+	__returnType = __get_ffi_type_uint32();
     } else if (returnTypeSymbol == @symbol(uint64)) {
-        __returnType = __get_ffi_type_uint64();
+	__returnType = __get_ffi_type_uint64();
 
     } else if (returnTypeSymbol == @symbol(sint)) {
-        __returnType = __get_ffi_type_sint();
+	__returnType = __get_ffi_type_sint();
     } else if (returnTypeSymbol == @symbol(sint8)) {
-        __returnType = __get_ffi_type_sint8();
+	__returnType = __get_ffi_type_sint8();
     } else if (returnTypeSymbol == @symbol(sint16)) {
-        __returnType = __get_ffi_type_sint16();
+	__returnType = __get_ffi_type_sint16();
     } else if (returnTypeSymbol == @symbol(sint32)) {
-        __returnType = __get_ffi_type_sint32();
+	__returnType = __get_ffi_type_sint32();
     } else if (returnTypeSymbol == @symbol(sint64)) {
-        __returnType = __get_ffi_type_sint64();
+	__returnType = __get_ffi_type_sint64();
 
     } else if (returnTypeSymbol == @symbol(long)) {
-        if (sizeof(long) == 4) {
-           returnTypeSymbol = @symbol(sint32);
-           __returnType = __get_ffi_type_sint32();
-        } else if (sizeof(long) == 8) {
-           returnTypeSymbol = @symbol(sint64);
-           __returnType = __get_ffi_type_sint64();
-        } else {
-            __FAIL__(@symbol(UnknownReturnType))
-        }
+	if (sizeof(long) == 4) {
+	   returnTypeSymbol = @symbol(sint32);
+	   __returnType = __get_ffi_type_sint32();
+	} else if (sizeof(long) == 8) {
+	   returnTypeSymbol = @symbol(sint64);
+	   __returnType = __get_ffi_type_sint64();
+	} else {
+	    __FAIL__(@symbol(UnknownReturnType))
+	}
 
     } else if (returnTypeSymbol == @symbol(ulong)) {
-        if (sizeof(long) == 4) {
-           returnTypeSymbol = @symbol(uint32);
-           __returnType = __get_ffi_type_uint32();
-        }else if (sizeof(long) == 8) {
-           returnTypeSymbol = @symbol(uint64);
-           __returnType = __get_ffi_type_uint64();
-        } else {
-            __FAIL__(@symbol(UnknownReturnType))
-        }
+	if (sizeof(long) == 4) {
+	   returnTypeSymbol = @symbol(uint32);
+	   __returnType = __get_ffi_type_uint32();
+	}else if (sizeof(long) == 8) {
+	   returnTypeSymbol = @symbol(uint64);
+	   __returnType = __get_ffi_type_uint64();
+	} else {
+	    __FAIL__(@symbol(UnknownReturnType))
+	}
 
     } else if (returnTypeSymbol == @symbol(bool)) {
-        __returnType = __get_ffi_type_uint();
+	__returnType = __get_ffi_type_uint();
 
     } else if (returnTypeSymbol == @symbol(float)) {
-        __returnType = __get_ffi_type_float();
+	__returnType = __get_ffi_type_float();
     } else if (returnTypeSymbol == @symbol(double)) {
-        __returnType = __get_ffi_type_double();
+	__returnType = __get_ffi_type_double();
 
     } else if (returnTypeSymbol == @symbol(void)) {
-        __returnType = __get_ffi_type_void();
-        __returnValuePointer = NULL;
+	__returnType = __get_ffi_type_void();
+	__returnValuePointer = NULL;
     } else if ((returnTypeSymbol == @symbol(pointer))
-               || (returnTypeSymbol == @symbol(handle))
-               || (returnTypeSymbol == @symbol(charPointer))
-               || (returnTypeSymbol == @symbol(bytePointer))
-               || (returnTypeSymbol == @symbol(floatPointer))
-               || (returnTypeSymbol == @symbol(doublePointer))
-               || (returnTypeSymbol == @symbol(intPointer))
-               || (returnTypeSymbol == @symbol(shortPointer))
-               || (returnTypeSymbol == @symbol(wcharPointer))) {
-        __returnType = __get_ffi_type_pointer();
+	       || (returnTypeSymbol == @symbol(handle))
+	       || (returnTypeSymbol == @symbol(charPointer))
+	       || (returnTypeSymbol == @symbol(bytePointer))
+	       || (returnTypeSymbol == @symbol(floatPointer))
+	       || (returnTypeSymbol == @symbol(doublePointer))
+	       || (returnTypeSymbol == @symbol(intPointer))
+	       || (returnTypeSymbol == @symbol(shortPointer))
+	       || (returnTypeSymbol == @symbol(wcharPointer))) {
+	__returnType = __get_ffi_type_pointer();
     } else {
-        if (__isSymbol(returnTypeSymbol)
-         && ((returnValueClass = __GLOBAL_GET(returnTypeSymbol)) != nil)) {
-            if (! __isBehaviorLike(returnValueClass)) {
-                __FAIL__(@symbol(NonBehaviorReturnType))
-            }
-            if (! __qIsSubclassOfExternalAddress(returnValueClass)) {
-                __FAIL__(@symbol(NonExternalAddressReturnType))
-            }
-            __returnType = __get_ffi_type_pointer();
-            returnTypeSymbol = @symbol(pointer);
-        } else {
-            __FAIL__(@symbol(UnknownReturnType))
-        }
+	if (__isSymbol(returnTypeSymbol)
+	 && ((returnValueClass = __GLOBAL_GET(returnTypeSymbol)) != nil)) {
+	    if (! __isBehaviorLike(returnValueClass)) {
+		__FAIL__(@symbol(NonBehaviorReturnType))
+	    }
+	    if (! __qIsSubclassOfExternalAddress(returnValueClass)) {
+		__FAIL__(@symbol(NonExternalAddressReturnType))
+	    }
+	    __returnType = __get_ffi_type_pointer();
+	    returnTypeSymbol = @symbol(pointer);
+	} else {
+	    __FAIL__(@symbol(UnknownReturnType))
+	}
     }
 
     /*
      * validate the c++ object
      */
     if (aReceiverOrNil != nil) {
-        struct cPlusPlusInstance {
-            void **vTable;
-        };
-        struct cPlusPlusInstance *inst;
+	struct cPlusPlusInstance {
+	    void **vTable;
+	};
+	struct cPlusPlusInstance *inst;
 
-        if (__isExternalAddressLike(aReceiverOrNil)) {
-            inst = (void *)(__externalAddressVal(aReceiverOrNil));
-        } else if (__isExternalBytesLike(aReceiverOrNil)) {
-            inst = (void *)(__externalBytesVal(aReceiverOrNil));
-        } else {
-            __FAIL__(@symbol(InvalidInstance))
-        }
-        __argValues[0].pointerVal = inst;
-        __argValuePointersIncludingThis[0] = &(__argValues[0]);
-        __argTypes[0] = __get_ffi_type_pointer();
+	if (__isExternalAddressLike(aReceiverOrNil)) {
+	    inst = (void *)(__externalAddressVal(aReceiverOrNil));
+	} else if (__isExternalBytesLike(aReceiverOrNil)) {
+	    inst = (void *)(__externalBytesVal(aReceiverOrNil));
+	} else {
+	    __FAIL__(@symbol(InvalidInstance))
+	}
+	__argValues[0].pointerVal = inst;
+	__argValuePointersIncludingThis[0] = &(__argValues[0]);
+	__argTypes[0] = __get_ffi_type_pointer();
 
-        __argValuePointers = &__argValuePointersIncludingThis[1];
-        __argTypes = &__argTypesIncludingThis[1];
-        __argValues = &__argValuesIncludingThis[1];
-        __numArgsIncludingThis = __numArgs + 1;
+	__argValuePointers = &__argValuePointersIncludingThis[1];
+	__argTypes = &__argTypesIncludingThis[1];
+	__argValues = &__argValuesIncludingThis[1];
+	__numArgsIncludingThis = __numArgs + 1;
 
-        if (virtual == true) {
-            if (! __isSmallInteger(vtOffset)) {
-                __FAIL__(@symbol(InvalidVTableIndex))
-            }
-            codeAddress = inst->vTable[__intVal(vtOffset)];
+	if (virtual == true) {
+	    if (! __isSmallInteger(vtOffset)) {
+		__FAIL__(@symbol(InvalidVTableIndex))
+	    }
+	    codeAddress = inst->vTable[__intVal(vtOffset)];
 # ifdef VERBOSE
-            if (@global(Verbose) == true) {
-                printf("virtual %d codeAddress: %"_lx_"\n", __intVal(vtOffset), (INT)codeAddress);
-            }
+	    if (@global(Verbose) == true) {
+		printf("virtual %d codeAddress: %"_lx_"\n", __intVal(vtOffset), (INT)codeAddress);
+	    }
 # endif
-        }
+	}
     } else {
-        __numArgsIncludingThis = __numArgs;
+	__numArgsIncludingThis = __numArgs;
 # ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("codeAddress: %"_lx_"\n", (INT)codeAddress);
-        }
+	if (@global(Verbose) == true) {
+	    printf("codeAddress: %"_lx_"\n", (INT)codeAddress);
+	}
 # endif
     }
 
@@ -1206,514 +1221,514 @@
      * validate all arg types, map each to an ffi_type, and setup arg-buffers
      */
     for (i=0; i<__numArgs; i++) {
-        ffi_type *thisType;
-        void *argValuePtr;
-        OBJ typeSymbol;
-        OBJ arg;
+	ffi_type *thisType;
+	void *argValuePtr;
+	OBJ typeSymbol;
+	OBJ arg;
 
-        failureInfo = __mkSmallInteger(i+1);   /* in case there is one */
+	failureInfo = __mkSmallInteger(i+1);   /* in case there is one */
 
-        typeSymbol = __ArrayInstPtr(argTypeSymbols)->a_element[i];
-        arg = __ArrayInstPtr(argumentsOrNil)->a_element[i];
+	typeSymbol = __ArrayInstPtr(argTypeSymbols)->a_element[i];
+	arg = __ArrayInstPtr(argumentsOrNil)->a_element[i];
 
-        if (typeSymbol == @symbol(handle)) {
-            typeSymbol = @symbol(pointer);
-        } else if (typeSymbol == @symbol(voidPointer)) {
-            typeSymbol = @symbol(pointer);
-        } else if (returnTypeSymbol == @symbol(hresult)) {
-            typeSymbol = @symbol(uint32);
-        }
+	if (typeSymbol == @symbol(handle)) {
+	    typeSymbol = @symbol(pointer);
+	} else if (typeSymbol == @symbol(voidPointer)) {
+	    typeSymbol = @symbol(pointer);
+	} else if (returnTypeSymbol == @symbol(hresult)) {
+	    typeSymbol = @symbol(uint32);
+	}
 
-        if (typeSymbol == @symbol(long)) {
-            if (sizeof(long) == sizeof(int)) {
-                typeSymbol = @symbol(sint);
-            } else {
-                if (sizeof(long) == 4) {
-                    typeSymbol = @symbol(sint32);
-                } else if (sizeof(long) == 8) {
-                    typeSymbol = @symbol(sint64);
-                }
-            }
-        }
-        if (typeSymbol == @symbol(ulong)) {
-            if (sizeof(unsigned long) == sizeof(unsigned int)) {
-                typeSymbol = @symbol(uint);
-            } else {
-                if (sizeof(long) == 4) {
-                    typeSymbol = @symbol(uint32);
-                } else if (sizeof(long) == 8) {
-                    typeSymbol = @symbol(uint64);
-                }
-            }
-        }
+	if (typeSymbol == @symbol(long)) {
+	    if (sizeof(long) == sizeof(int)) {
+		typeSymbol = @symbol(sint);
+	    } else {
+		if (sizeof(long) == 4) {
+		    typeSymbol = @symbol(sint32);
+		} else if (sizeof(long) == 8) {
+		    typeSymbol = @symbol(sint64);
+		}
+	    }
+	}
+	if (typeSymbol == @symbol(ulong)) {
+	    if (sizeof(unsigned long) == sizeof(unsigned int)) {
+		typeSymbol = @symbol(uint);
+	    } else {
+		if (sizeof(long) == 4) {
+		    typeSymbol = @symbol(uint32);
+		} else if (sizeof(long) == 8) {
+		    typeSymbol = @symbol(uint64);
+		}
+	    }
+	}
 
-        if (typeSymbol == @symbol(int) || typeSymbol == @symbol(sint)) {
-            thisType = __get_ffi_type_sint();
-            if (__isSmallInteger(arg)) {
-                __argValues[i].iVal = __intVal(arg);
-            } else {
-                __argValues[i].iVal = __signedLongIntVal(arg);
-                if (__argValues[i].iVal == 0) {
+	if (typeSymbol == @symbol(int) || typeSymbol == @symbol(sint)) {
+	    thisType = __get_ffi_type_sint();
+	    if (__isSmallInteger(arg)) {
+		__argValues[i].iVal = __intVal(arg);
+	    } else {
+		__argValues[i].iVal = __signedLongIntVal(arg);
+		if (__argValues[i].iVal == 0) {
 # ifdef VERBOSE
-                        if (@global(Verbose) == true) {
-                            printf("invalidArgument: arg%d sint value out of range [%d]\n", i+1, __LINE__);
-                        }
+			if (@global(Verbose) == true) {
+			    printf("invalidArgument: arg%d sint value out of range [%d]\n", i+1, __LINE__);
+			}
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].iVal);
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
 
-        } else if (typeSymbol == @symbol(uint)) {
-            thisType = __get_ffi_type_uint();
+	} else if (typeSymbol == @symbol(uint)) {
+	    thisType = __get_ffi_type_uint();
 
-            if (__isSmallInteger(arg)) {
-                __argValues[i].iVal = __intVal(arg);
-            } else {
-                __argValues[i].iVal = __unsignedLongIntVal(arg);
-                if (__argValues[i].iVal == 0) {
+	    if (__isSmallInteger(arg)) {
+		__argValues[i].iVal = __intVal(arg);
+	    } else {
+		__argValues[i].iVal = __unsignedLongIntVal(arg);
+		if (__argValues[i].iVal == 0) {
 # ifdef VERBOSE
-                        if (@global(Verbose) == true) {
-                            printf("invalidArgument: arg%d uint value out of range [%d]\n", i+1, __LINE__);
-                        }
+			if (@global(Verbose) == true) {
+			    printf("invalidArgument: arg%d uint value out of range [%d]\n", i+1, __LINE__);
+			}
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].iVal);
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
 
-        } else if (typeSymbol == @symbol(uint8)) {
-            thisType = __get_ffi_type_uint8();
-            if (! __isSmallInteger(arg)) {
+	} else if (typeSymbol == @symbol(uint8)) {
+	    thisType = __get_ffi_type_uint8();
+	    if (! __isSmallInteger(arg)) {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d uint8 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d uint8 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            __argValues[i].iVal = __intVal(arg);
-            if (((unsigned)(__argValues[i].iVal)) > 0xFF) {
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    __argValues[i].iVal = __intVal(arg);
+	    if (((unsigned)(__argValues[i].iVal)) > 0xFF) {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d uint8 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d uint8 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            argValuePtr = &(__argValues[i].iVal);
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
 
-        } else if (typeSymbol == @symbol(sint8)) {
-            thisType = __get_ffi_type_sint8();
-            if (! __isSmallInteger(arg)) {
+	} else if (typeSymbol == @symbol(sint8)) {
+	    thisType = __get_ffi_type_sint8();
+	    if (! __isSmallInteger(arg)) {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d sint8 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d sint8 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            __argValues[i].iVal = __intVal(arg);
-            if (((__argValues[i].iVal) < -0x80) || ((__argValues[i].iVal) > 0x7F))  {
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    __argValues[i].iVal = __intVal(arg);
+	    if (((__argValues[i].iVal) < -0x80) || ((__argValues[i].iVal) > 0x7F))  {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d sint8 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d sint8 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            argValuePtr = &(__argValues[i].iVal);
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
 
-        } else if (typeSymbol == @symbol(uint16)) {
-            thisType = __get_ffi_type_uint16();
-            if (! __isSmallInteger(arg)) {
+	} else if (typeSymbol == @symbol(uint16)) {
+	    thisType = __get_ffi_type_uint16();
+	    if (! __isSmallInteger(arg)) {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d uint16 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d uint16 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            __argValues[i].iVal = __intVal(arg);
-            if (((unsigned)(__argValues[i].iVal)) > 0xFFFF) {
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    __argValues[i].iVal = __intVal(arg);
+	    if (((unsigned)(__argValues[i].iVal)) > 0xFFFF) {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d uint16 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d uint16 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            argValuePtr = &(__argValues[i].iVal);
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
 
-        } else if (typeSymbol == @symbol(sint16)) {
-            thisType = __get_ffi_type_sint16();
-            if (! __isSmallInteger(arg)) {
+	} else if (typeSymbol == @symbol(sint16)) {
+	    thisType = __get_ffi_type_sint16();
+	    if (! __isSmallInteger(arg)) {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d sint16 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d sint16 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            __argValues[i].iVal = __intVal(arg);
-            if (((__argValues[i].iVal) < -0x8000) || ((__argValues[i].iVal) > 0x7FFF))  {
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    __argValues[i].iVal = __intVal(arg);
+	    if (((__argValues[i].iVal) < -0x8000) || ((__argValues[i].iVal) > 0x7FFF))  {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d sint16 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d sint16 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            argValuePtr = &(__argValues[i].iVal);
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
 
-        } else if (typeSymbol == @symbol(uint32)) {
-            thisType = __get_ffi_type_uint32();
-            if (__isSmallInteger(arg)) {
-                __argValues[i].iVal = __intVal(arg);
-            } else {
-                __argValues[i].iVal = __unsignedLongIntVal(arg);
-                if (__argValues[i].iVal == 0) {
+	} else if (typeSymbol == @symbol(uint32)) {
+	    thisType = __get_ffi_type_uint32();
+	    if (__isSmallInteger(arg)) {
+		__argValues[i].iVal = __intVal(arg);
+	    } else {
+		__argValues[i].iVal = __unsignedLongIntVal(arg);
+		if (__argValues[i].iVal == 0) {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d uint32 value out of range [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d uint32 value out of range [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
 # if __POINTER_SIZE__ == 8
-            if ((__argValues[i].iVal) < 0)  {
+	    if ((__argValues[i].iVal) < 0)  {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d uint32 value out of range [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d uint32 value out of range [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
+		__FAIL__(@symbol(InvalidArgument))
+	    }
 # endif
-            argValuePtr = &(__argValues[i].iVal);
+	    argValuePtr = &(__argValues[i].iVal);
 
-         } else if (typeSymbol == @symbol(sint32)) {
-            thisType = __get_ffi_type_uint32();
-            if (__isSmallInteger(arg)) {
-                __argValues[i].iVal = __intVal(arg);
-            } else {
-                __argValues[i].iVal = __signedLongIntVal(arg);
-                if (__argValues[i].iVal == 0) {
+	 } else if (typeSymbol == @symbol(sint32)) {
+	    thisType = __get_ffi_type_uint32();
+	    if (__isSmallInteger(arg)) {
+		__argValues[i].iVal = __intVal(arg);
+	    } else {
+		__argValues[i].iVal = __signedLongIntVal(arg);
+		if (__argValues[i].iVal == 0) {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d sint32 value out of range [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d sint32 value out of range [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
 # if __POINTER_SIZE__ == 8
-            if (((__argValues[i].iVal) < -0x80000000LL) || ((__argValues[i].iVal) > 0x7FFFFFFFLL))  {
+	    if (((__argValues[i].iVal) < -0x80000000LL) || ((__argValues[i].iVal) > 0x7FFFFFFFLL))  {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d sint32 value (%"_lx_") out of range [%d]\n", i+1, __argValues[i].iVal, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d sint32 value (%"_lx_") out of range [%d]\n", i+1, __argValues[i].iVal, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
+		__FAIL__(@symbol(InvalidArgument))
+	    }
 # endif
-            argValuePtr = &(__argValues[i].iVal);
+	    argValuePtr = &(__argValues[i].iVal);
 
-        } else if (typeSymbol == @symbol(uint64)) {
-            thisType = __get_ffi_type_uint64();
-            if (__isSmallInteger(arg)) {
-                __argValues[i].iVal = __intVal(arg);
-            } else {
-                __argValues[i].iVal = __unsignedLongIntVal(arg);
-                if (__argValues[i].iVal == 0) {
+	} else if (typeSymbol == @symbol(uint64)) {
+	    thisType = __get_ffi_type_uint64();
+	    if (__isSmallInteger(arg)) {
+		__argValues[i].iVal = __intVal(arg);
+	    } else {
+		__argValues[i].iVal = __unsignedLongIntVal(arg);
+		if (__argValues[i].iVal == 0) {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d uint64 value out of range [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d uint64 value out of range [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].iVal);
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
 
-         } else if (typeSymbol == @symbol(sint64)) {
-            thisType = __get_ffi_type_sint64();
-            if (__isSmallInteger(arg)) {
-                __argValues[i].iVal = __intVal(arg);
-            } else {
-                __argValues[i].iVal = __signedLongIntVal(arg);
-                if (__argValues[i].iVal == 0) {
+	 } else if (typeSymbol == @symbol(sint64)) {
+	    thisType = __get_ffi_type_sint64();
+	    if (__isSmallInteger(arg)) {
+		__argValues[i].iVal = __intVal(arg);
+	    } else {
+		__argValues[i].iVal = __signedLongIntVal(arg);
+		if (__argValues[i].iVal == 0) {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d sint64 value out of range [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d sint64 value out of range [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].iVal);
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
 
-        } else if (typeSymbol == @symbol(float)) {
-            thisType = __get_ffi_type_float();
-            if (__isSmallInteger(arg)) {
-                __argValues[i].fVal = (float)(__intVal(arg));
-            } else if (__isFloat(arg)) {
-                __argValues[i].fVal = (float)(__floatVal(arg));
-            } else if (__isShortFloat(arg)) {
-                __argValues[i].fVal = (float)(__shortFloatVal(arg));
-            } else {
+	} else if (typeSymbol == @symbol(float)) {
+	    thisType = __get_ffi_type_float();
+	    if (__isSmallInteger(arg)) {
+		__argValues[i].fVal = (float)(__intVal(arg));
+	    } else if (__isFloat(arg)) {
+		__argValues[i].fVal = (float)(__floatVal(arg));
+	    } else if (__isShortFloat(arg)) {
+		__argValues[i].fVal = (float)(__shortFloatVal(arg));
+	    } else {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d non float value [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d non float value [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            argValuePtr = &(__argValues[i].fVal);
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    argValuePtr = &(__argValues[i].fVal);
 
-        } else if (typeSymbol == @symbol(double)) {
-            thisType = __get_ffi_type_double();
-            if (__isSmallInteger(arg)) {
-                __argValues[i].dVal = (double)(__intVal(arg));
-            } else if (__isFloat(arg)) {
-                __argValues[i].dVal = (double)(__floatVal(arg));
-            } else if (__isShortFloat(arg)) {
-                __argValues[i].dVal = (double)(__shortFloatVal(arg));
-            } else {
+	} else if (typeSymbol == @symbol(double)) {
+	    thisType = __get_ffi_type_double();
+	    if (__isSmallInteger(arg)) {
+		__argValues[i].dVal = (double)(__intVal(arg));
+	    } else if (__isFloat(arg)) {
+		__argValues[i].dVal = (double)(__floatVal(arg));
+	    } else if (__isShortFloat(arg)) {
+		__argValues[i].dVal = (double)(__shortFloatVal(arg));
+	    } else {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d non double value [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d non double value [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            argValuePtr = &(__argValues[i].dVal);
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    argValuePtr = &(__argValues[i].dVal);
 
-        } else if (typeSymbol == @symbol(void)) {
-            thisType = __get_ffi_type_void();
-            argValuePtr = &null;
+	} else if (typeSymbol == @symbol(void)) {
+	    thisType = __get_ffi_type_void();
+	    argValuePtr = &null;
 
-        } else if (typeSymbol == @symbol(charPointer)) {
-            thisType = __get_ffi_type_pointer();
-            if (__isStringLike(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__stringVal(arg));
-            } else if (__isBytes(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
-            } else if (__isExternalAddressLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
-            } else if (__isExternalBytesLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
-            } else {
-                if (arg == nil) {
-                    __argValues[i].pointerVal = (void *)0;
-                } else {
+	} else if (typeSymbol == @symbol(charPointer)) {
+	    thisType = __get_ffi_type_pointer();
+	    if (__isStringLike(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__stringVal(arg));
+	    } else if (__isBytes(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
+	    } else if (__isExternalAddressLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
+	    } else if (__isExternalBytesLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
+	    } else {
+		if (arg == nil) {
+		    __argValues[i].pointerVal = (void *)0;
+		} else {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d non charPointer value [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d non charPointer value [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].pointerVal);;
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].pointerVal);;
 
-        } else if (typeSymbol == @symbol(wcharPointer)) {
-            thisType = __get_ffi_type_pointer();
-            if (__isUnicode16String(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__unicode16StringVal(arg));
-            } else if (__isBytes(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
-            } else if (__isExternalAddressLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
-            } else if (__isExternalBytesLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
-            } else {
-                if (arg == nil) {
-                    __argValues[i].pointerVal = (void *)0;
-                } else {
+	} else if (typeSymbol == @symbol(wcharPointer)) {
+	    thisType = __get_ffi_type_pointer();
+	    if (__isUnicode16String(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__unicode16StringVal(arg));
+	    } else if (__isBytes(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
+	    } else if (__isExternalAddressLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
+	    } else if (__isExternalBytesLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
+	    } else {
+		if (arg == nil) {
+		    __argValues[i].pointerVal = (void *)0;
+		} else {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d non wcharPointer value [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d non wcharPointer value [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].pointerVal);;
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].pointerVal);;
 
-        } else if (typeSymbol == @symbol(floatPointer)) {
-            thisType = __get_ffi_type_pointer();
-            if (__isBytes(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
-            } else if (__isExternalAddressLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
-            } else if (__isExternalBytesLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
-            } else if (__isFloats(arg)) {
-                char *p = (char *)(__FloatArrayInstPtr(arg)->f_element);
-                int nInstBytes;
-                OBJ cls;
+	} else if (typeSymbol == @symbol(floatPointer)) {
+	    thisType = __get_ffi_type_pointer();
+	    if (__isBytes(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
+	    } else if (__isExternalAddressLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
+	    } else if (__isExternalBytesLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
+	    } else if (__isFloats(arg)) {
+		char *p = (char *)(__FloatArrayInstPtr(arg)->f_element);
+		int nInstBytes;
+		OBJ cls;
 
-                if (async == true) goto badArgForAsyncCall;
-                cls = __qClass(arg);
-                nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-                p = p + nInstBytes;
-                __argValues[i].pointerVal = p;
-            } else {
-                if (arg == nil) {
-                    __argValues[i].pointerVal = (void *)0;
-                } else {
+		if (async == true) goto badArgForAsyncCall;
+		cls = __qClass(arg);
+		nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+		p = p + nInstBytes;
+		__argValues[i].pointerVal = p;
+	    } else {
+		if (arg == nil) {
+		    __argValues[i].pointerVal = (void *)0;
+		} else {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d non floatPointer value [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d non floatPointer value [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].pointerVal);;
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].pointerVal);;
 
-        } else if (typeSymbol == @symbol(doublePointer)) {
-            thisType = __get_ffi_type_pointer();
-            if (__isBytes(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
-            } else if (__isExternalAddressLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
-            } else if (__isExternalBytesLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
-            } else if (__isDoubles(arg)) {
-                char *p = (char *)(__DoubleArrayInstPtr(arg)->d_element);
-                int nInstBytes;
-                OBJ cls;
+	} else if (typeSymbol == @symbol(doublePointer)) {
+	    thisType = __get_ffi_type_pointer();
+	    if (__isBytes(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
+	    } else if (__isExternalAddressLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
+	    } else if (__isExternalBytesLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
+	    } else if (__isDoubles(arg)) {
+		char *p = (char *)(__DoubleArrayInstPtr(arg)->d_element);
+		int nInstBytes;
+		OBJ cls;
 
-                if (async == true) goto badArgForAsyncCall;
-                cls = __qClass(arg);
-                nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-                p = p + nInstBytes;
+		if (async == true) goto badArgForAsyncCall;
+		cls = __qClass(arg);
+		nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+		p = p + nInstBytes;
 # ifdef __NEED_DOUBLE_ALIGN
-                if ((INT)(__DoubleArrayInstPtr(arg)->d_element) & (__DOUBLE_ALIGN-1)) {
-                    int delta = __DOUBLE_ALIGN - ((INT)p & (__DOUBLE_ALIGN-1));
+		if ((INT)(__DoubleArrayInstPtr(arg)->d_element) & (__DOUBLE_ALIGN-1)) {
+		    int delta = __DOUBLE_ALIGN - ((INT)p & (__DOUBLE_ALIGN-1));
 
-                    p += delta;
-                }
+		    p += delta;
+		}
 # endif
-                __argValues[i].pointerVal = p;
-            } else {
-                if (arg == nil) {
-                    __argValues[i].pointerVal = (void *)0;
-                } else {
+		__argValues[i].pointerVal = p;
+	    } else {
+		if (arg == nil) {
+		    __argValues[i].pointerVal = (void *)0;
+		} else {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d non doublePointer value [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d non doublePointer value [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].pointerVal);;
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].pointerVal);;
 
-        } else if (typeSymbol == @symbol(pointer)) {
+	} else if (typeSymbol == @symbol(pointer)) {
 commonPointerTypeArg: ;
-            thisType = __get_ffi_type_pointer();
-            if (arg == nil) {
-                __argValues[i].pointerVal = NULL;
-            } else if (__isExternalAddressLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
-            } else if (__isExternalBytesLike(arg)) {
-                __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
-            } else if (__isByteArrayLike(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
-            } else if (__isWordArray(arg) || __isSignedWordArray(arg)
-                    || __isIntegerArray(arg) || __isSignedIntegerArray(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__integerArrayVal(arg));
-            } else if (__isFloatArray(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__FloatArrayInstPtr(arg)->f_element);
-            } else if (__isDoubleArray(arg)) {
-                if (async == true) goto badArgForAsyncCall;
-                __argValues[i].pointerVal = (void *)(__DoubleArrayInstPtr(arg)->d_element);
-            } else if (__isStringLike(arg)) {
-                if (async == true) {
+	    thisType = __get_ffi_type_pointer();
+	    if (arg == nil) {
+		__argValues[i].pointerVal = NULL;
+	    } else if (__isExternalAddressLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
+	    } else if (__isExternalBytesLike(arg)) {
+		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
+	    } else if (__isByteArrayLike(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
+	    } else if (__isWordArray(arg) || __isSignedWordArray(arg)
+		    || __isIntegerArray(arg) || __isSignedIntegerArray(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__integerArrayVal(arg));
+	    } else if (__isFloatArray(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__FloatArrayInstPtr(arg)->f_element);
+	    } else if (__isDoubleArray(arg)) {
+		if (async == true) goto badArgForAsyncCall;
+		__argValues[i].pointerVal = (void *)(__DoubleArrayInstPtr(arg)->d_element);
+	    } else if (__isStringLike(arg)) {
+		if (async == true) {
 badArgForAsyncCall: ;
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d not allowed for async call [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d not allowed for async call [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(BadArgForAsyncCall))
-                }
-                __argValues[i].pointerVal = (void *)(__stringVal(arg));
-            } else if (__isBytes(arg) || __isWords(arg) || __isLongs(arg)) {
-                char *p = (char *)(__byteArrayVal(arg));
-                int nInstBytes;
-                OBJ cls;
+		    __FAIL__(@symbol(BadArgForAsyncCall))
+		}
+		__argValues[i].pointerVal = (void *)(__stringVal(arg));
+	    } else if (__isBytes(arg) || __isWords(arg) || __isLongs(arg)) {
+		char *p = (char *)(__byteArrayVal(arg));
+		int nInstBytes;
+		OBJ cls;
 
-                if (async == true) goto badArgForAsyncCall;
-                cls = __qClass(arg);
-                nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
-                __argValues[i].pointerVal = p + nInstBytes;
-            } else {
+		if (async == true) goto badArgForAsyncCall;
+		cls = __qClass(arg);
+		nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
+		__argValues[i].pointerVal = p + nInstBytes;
+	    } else {
 # ifdef VERBOSE
-                if (@global(Verbose) == true) {
-                    printf("invalidArgument: arg%d non pointer value [%d]\n", i+1, __LINE__);
-                }
+		if (@global(Verbose) == true) {
+		    printf("invalidArgument: arg%d non pointer value [%d]\n", i+1, __LINE__);
+		}
 # endif
-                __FAIL__(@symbol(InvalidArgument))
-            }
-            argValuePtr = &(__argValues[i].pointerVal);;
+		__FAIL__(@symbol(InvalidArgument))
+	    }
+	    argValuePtr = &(__argValues[i].pointerVal);;
 
-        } else if (typeSymbol == @symbol(bool)) {
-            thisType = __get_ffi_type_uint();
+	} else if (typeSymbol == @symbol(bool)) {
+	    thisType = __get_ffi_type_uint();
 
-            if (arg == true) {
-                __argValues[i].iVal = 1;
-            } else if (arg == false) {
-                __argValues[i].iVal = 0;
-            } else if (__isSmallInteger(arg)) {
-                __argValues[i].iVal = __intVal(arg);
-            } else {
-                __argValues[i].iVal = __unsignedLongIntVal(arg);
-                if (__argValues[i].iVal == 0) {
+	    if (arg == true) {
+		__argValues[i].iVal = 1;
+	    } else if (arg == false) {
+		__argValues[i].iVal = 0;
+	    } else if (__isSmallInteger(arg)) {
+		__argValues[i].iVal = __intVal(arg);
+	    } else {
+		__argValues[i].iVal = __unsignedLongIntVal(arg);
+		if (__argValues[i].iVal == 0) {
 # ifdef VERBOSE
-                    if (@global(Verbose) == true) {
-                        printf("invalidArgument: arg%d non bool value [%d]\n", i+1, __LINE__);
-                    }
+		    if (@global(Verbose) == true) {
+			printf("invalidArgument: arg%d non bool value [%d]\n", i+1, __LINE__);
+		    }
 # endif
-                    __FAIL__(@symbol(InvalidArgument))
-                }
-            }
-            argValuePtr = &(__argValues[i].iVal);
-        } else {
-            if (__isSymbol(typeSymbol)
-             && ((argValueClass = __GLOBAL_GET(typeSymbol)) != nil)) {
-                if (! __isBehaviorLike(argValueClass)) {
-                    __FAIL__(@symbol(NonBehaviorArgumentType))
-                }
-                if (! __qIsSubclassOfExternalAddress(argValueClass)) {
-                    __FAIL__(@symbol(NonExternalAddressArgumentType))
-                }
-                goto commonPointerTypeArg; /* sorry */
-            } else {
-                __FAIL__(@symbol(UnknownArgumentType))
-            }
-        }
+		    __FAIL__(@symbol(InvalidArgument))
+		}
+	    }
+	    argValuePtr = &(__argValues[i].iVal);
+	} else {
+	    if (__isSymbol(typeSymbol)
+	     && ((argValueClass = __GLOBAL_GET(typeSymbol)) != nil)) {
+		if (! __isBehaviorLike(argValueClass)) {
+		    __FAIL__(@symbol(NonBehaviorArgumentType))
+		}
+		if (! __qIsSubclassOfExternalAddress(argValueClass)) {
+		    __FAIL__(@symbol(NonExternalAddressArgumentType))
+		}
+		goto commonPointerTypeArg; /* sorry */
+	    } else {
+		__FAIL__(@symbol(UnknownArgumentType))
+	    }
+	}
 
-        __argTypes[i] = thisType;
-        __argValuePointers[i] = argValuePtr;
+	__argTypes[i] = thisType;
+	__argValuePointers[i] = argValuePtr;
 
 # ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("arg%d: %"_lx_" type:%"_lx_"\n", i+1, (INT)(__argValues[i].iVal), (INT)thisType);
-        }
+	if (@global(Verbose) == true) {
+	    printf("arg%d: %"_lx_" type:%"_lx_"\n", i+1, (INT)(__argValues[i].iVal), (INT)thisType);
+	}
 # endif
     }
     failureInfo = nil;
@@ -1722,66 +1737,66 @@
 
 # ifdef CALLTYPE_FFI_STDCALL
     if (callTypeNumber == @global(CALLTYPE_API)) {
-        __callType = CALLTYPE_FFI_STDCALL;
+	__callType = CALLTYPE_FFI_STDCALL;
 # ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("STDCALL\n");
-        }
+	if (@global(Verbose) == true) {
+	    printf("STDCALL\n");
+	}
 # endif
     }
 # endif
 # ifdef CALLTYPE_FFI_V8
     if (callTypeNumber == @global(CALLTYPE_V8)) {
-        __callType = CALLTYPE_FFI_V8;
+	__callType = CALLTYPE_FFI_V8;
     }
 # endif
 # ifdef CALLTYPE_FFI_V9
     if (callTypeNumber == @global(CALLTYPE_V9)) {
-        __callType = CALLTYPE_FFI_V9;
+	__callType = CALLTYPE_FFI_V9;
     }
 # endif
 # ifdef CALLTYPE_FFI_UNIX64
     if (callTypeNumber == @global(CALLTYPE_UNIX64)) {
-        __callType = CALLTYPE_FFI_UNIX64;
+	__callType = CALLTYPE_FFI_UNIX64;
     }
 # endif
 
     if (ffi_prep_cif(&__cif, __callType, __numArgsIncludingThis, __returnType, __argTypesIncludingThis) != FFI_OK) {
-        __FAIL__(@symbol(FFIPrepareFailed))
+	__FAIL__(@symbol(FFIPrepareFailed))
     }
     if (async == true) {
 # ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("async call 0x%"_lx_"\n", (INT)codeAddress);
-        }
+	if (@global(Verbose) == true) {
+	    printf("async call 0x%"_lx_"\n", (INT)codeAddress);
+	}
 # endif
 # ifdef WIN32
-        __STX_C_CALL4( "ffi_call", ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
+	__STX_C_CALL4( "ffi_call", ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
 # else
-        __BEGIN_INTERRUPTABLE__
-        ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
-        __END_INTERRUPTABLE__
+	__BEGIN_INTERRUPTABLE__
+	ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
+	__END_INTERRUPTABLE__
 # endif
     } else {
-        if (unlimitedStack == true) {
+	if (unlimitedStack == true) {
 # ifdef VERBOSE
-            if (@global(Verbose) == true) {
-                printf("UNLIMITEDSTACKCALL call 0x%"_lx_"\n", (INT)codeAddress);
-            }
+	    if (@global(Verbose) == true) {
+		printf("UNLIMITEDSTACKCALL call 0x%"_lx_"\n", (INT)codeAddress);
+	    }
 # endif
-            __UNLIMITEDSTACKCALL4__((OBJFUNC)ffi_call, (INT)(&__cif), (INT)codeAddress, (INT)__returnValuePointer, (INT)__argValuePointersIncludingThis);
-        } else {
+	    __UNLIMITEDSTACKCALL4__((OBJFUNC)ffi_call, (INT)(&__cif), (INT)codeAddress, (INT)__returnValuePointer, (INT)__argValuePointersIncludingThis);
+	} else {
 # ifdef VERBOSE
-            if (@global(Verbose) == true) {
-                printf("call 0x%"_lx_"\n", (INT)codeAddress);
-            }
+	    if (@global(Verbose) == true) {
+		printf("call 0x%"_lx_"\n", (INT)codeAddress);
+	    }
 # endif
-            ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
-        }
+	    ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
+	}
     }
 # ifdef VERBOSE
     if (@global(Verbose) == true) {
-        printf("retval is %"_ld_" (0x%"_lx_")\n", (INT)(__returnValue.iVal), (INT)(__returnValue.iVal));
+	printf("retval is %"_ld_" (0x%"_lx_")\n", (INT)(__returnValue.iVal), (INT)(__returnValue.iVal));
     }
 # endif
 
@@ -1791,80 +1806,80 @@
      || (returnTypeSymbol == @symbol(sint16))
      || (returnTypeSymbol == @symbol(sint32))) {
 # ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("return int: %x\n", __returnValue.iVal);
-        }
+	if (@global(Verbose) == true) {
+	    printf("return int: %x\n", __returnValue.iVal);
+	}
 # endif
-        RETURN ( __MKINT(__returnValue.iVal) );
+	RETURN ( __MKINT(__returnValue.iVal) );
     }
     if ((returnTypeSymbol == @symbol(uint))
      || (returnTypeSymbol == @symbol(uint8))
      || (returnTypeSymbol == @symbol(uint16))
      || (returnTypeSymbol == @symbol(uint32))) {
 # ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("return uint: %x\n", __returnValue.iVal);
-        }
+	if (@global(Verbose) == true) {
+	    printf("return uint: %x\n", __returnValue.iVal);
+	}
 # endif
-        RETURN ( __MKUINT(__returnValue.iVal) );
+	RETURN ( __MKUINT(__returnValue.iVal) );
     }
     if (returnTypeSymbol == @symbol(bool)) {
-        RETURN ( __returnValue.iVal ? true : false );
+	RETURN ( __returnValue.iVal ? true : false );
     }
     if (returnTypeSymbol == @symbol(float)) {
-        RETURN ( __MKFLOAT(__returnValue.fVal ));
+	RETURN ( __MKFLOAT(__returnValue.fVal ));
     }
     if (returnTypeSymbol == @symbol(double)) {
-        RETURN ( __MKFLOAT(__returnValue.dVal ));
+	RETURN ( __MKFLOAT(__returnValue.dVal ));
     }
     if (returnTypeSymbol == @symbol(void)) {
-        RETURN ( nil );
+	RETURN ( nil );
     }
     if (returnTypeSymbol == @symbol(char)) {
-        RETURN ( __MKCHARACTER(__returnValue.iVal & 0xFF) );
+	RETURN ( __MKCHARACTER(__returnValue.iVal & 0xFF) );
     }
     if (returnTypeSymbol == @symbol(wchar)) {
-        RETURN ( __MKUCHARACTER(__returnValue.iVal & 0xFFFF) );
+	RETURN ( __MKUCHARACTER(__returnValue.iVal & 0xFFFF) );
     }
     if (returnTypeSymbol == @symbol(sint64)) {
 # if (__POINTER_SIZE__ == 8)
 
 #  ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("return sint64: %"_lx_"\n", (INT)(__returnValue.longLongVal));
-        }
+	if (@global(Verbose) == true) {
+	    printf("return sint64: %"_lx_"\n", (INT)(__returnValue.longLongVal));
+	}
 #  endif
-        RETURN ( __MKINT(__returnValue.longLongVal) );
+	RETURN ( __MKINT(__returnValue.longLongVal) );
 # else
 #  ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("return sint64: %lx%08lx\n", __HI32(__returnValue.longLongVal), __LO32(__returnValue.longLongVal));
-        }
+	if (@global(Verbose) == true) {
+	    printf("return sint64: %lx%08lx\n", __HI32(__returnValue.longLongVal), __LO32(__returnValue.longLongVal));
+	}
 #  endif
-        RETURN ( __MKINT64(&__returnValue.longLongVal) );
+	RETURN ( __MKINT64(&__returnValue.longLongVal) );
 # endif
     }
     if (returnTypeSymbol == @symbol(uint64)) {
 # if (__POINTER_SIZE__ == 8)
 # ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("return uint64: %"_lx_"\n", (unsigned INT)(__returnValue.longLongVal));
-        }
+	if (@global(Verbose) == true) {
+	    printf("return uint64: %"_lx_"\n", (unsigned INT)(__returnValue.longLongVal));
+	}
 # endif
-        RETURN ( __MKUINT(__returnValue.longLongVal) );
+	RETURN ( __MKUINT(__returnValue.longLongVal) );
 # else
 #  ifdef VERBOSE
-        if (@global(Verbose) == true) {
-            printf("return sint64: %lx%08lx\n", __HI32(__returnValue.longLongVal), __LO32(__returnValue.longLongVal));
-        }
+	if (@global(Verbose) == true) {
+	    printf("return sint64: %lx%08lx\n", __HI32(__returnValue.longLongVal), __LO32(__returnValue.longLongVal));
+	}
 #  endif
-        RETURN ( __MKUINT64(&__returnValue.longLongVal) );
+	RETURN ( __MKUINT64(&__returnValue.longLongVal) );
 # endif
     }
 
 # ifdef VERBOSE
     if (@global(Verbose) == true) {
-        printf("return pointer: %"_lx_"\n", (INT)(__returnValue.pointerVal));
+	printf("return pointer: %"_lx_"\n", (INT)(__returnValue.pointerVal));
     }
 # endif
     if (returnTypeSymbol == @symbol(handle) || returnTypeSymbol == @symbol(pointer)) {
@@ -1878,17 +1893,17 @@
                 (_initialize_ilc.ilc_func)(returnValue, @symbol(initialize), nil, &_initialize_ilc);
                 RETURN ( returnValue );
             } else {
-        returnValue = __MKEXTERNALADDRESS(__returnValue.pointerVal);
+	returnValue = __MKEXTERNALADDRESS(__returnValue.pointerVal);
             }
         }
     } else if (returnTypeSymbol == @symbol(bytePointer)) {
-        returnValue = __MKEXTERNALBYTES(__returnValue.pointerVal);
+	returnValue = __MKEXTERNALBYTES(__returnValue.pointerVal);
     } else if (returnTypeSymbol == @symbol(charPointer)) {
-        returnValue = __MKSTRING(__returnValue.pointerVal);
+	returnValue = __MKSTRING(__returnValue.pointerVal);
     } else if (returnTypeSymbol == @symbol(wcharPointer)) {
-        returnValue = __MKU16STRING(__returnValue.pointerVal);
+	returnValue = __MKU16STRING(__returnValue.pointerVal);
     } else {
-        __FAIL__(@symbol(UnknownReturnType2))
+	__FAIL__(@symbol(UnknownReturnType2))
     }
 #else /* no FFI support */
     failureCode = @symbol(FFINotSupported);
@@ -1896,49 +1911,49 @@
 getOutOfHere: ;
 %}.
     failureCode notNil ifTrue:[
-        (failureCode == #UnknownReturnType or:[ failureCode == #UnknownArgumentType ]) ifTrue:[
-            oldReturnType := returnType.
-            oldArgumentTypes := argumentTypes.
-            self adjustTypes.
-            ((oldReturnType ~= returnType) or:[oldArgumentTypes ~= argumentTypes]) ifTrue:[
-                thisContext restart
-            ].
-        ].
-        (failureCode == #BadArgForAsyncCall) ifTrue:[
-            ^ self tryAgainWithAsyncSafeArguments:argumentsOrNil forCPPInstance:aReceiverOrNil
-        ].
-        (failureCode == #FFINotSupported) ifTrue:[
-            self primitiveFailed:'FFI support missing in this build'.
-        ].
+	(failureCode == #UnknownReturnType or:[ failureCode == #UnknownArgumentType ]) ifTrue:[
+	    oldReturnType := returnType.
+	    oldArgumentTypes := argumentTypes.
+	    self adjustTypes.
+	    ((oldReturnType ~= returnType) or:[oldArgumentTypes ~= argumentTypes]) ifTrue:[
+		thisContext restart
+	    ].
+	].
+	(failureCode == #BadArgForAsyncCall) ifTrue:[
+	    ^ self tryAgainWithAsyncSafeArguments:argumentsOrNil forCPPInstance:aReceiverOrNil
+	].
+	(failureCode == #FFINotSupported) ifTrue:[
+	    self primitiveFailed:'FFI support missing in this build'.
+	].
 
-        self primitiveFailed.   "see failureCode and failureInfo for details"
-        ^ nil
+	self primitiveFailed.   "see failureCode and failureInfo for details"
+	^ nil
     ].
 
     returnType isSymbol ifTrue:[
-        returnValueClass notNil ifTrue:[
-            self isConstReturnValue ifTrue:[
-                returnValue changeClassTo:returnValueClass.
-                ^ returnValue
-            ].
-            ^ returnValueClass fromExternalAddress:returnValue.
-        ].
+	returnValueClass notNil ifTrue:[
+	    self isConstReturnValue ifTrue:[
+		returnValue changeClassTo:returnValueClass.
+		^ returnValue
+	    ].
+	    ^ returnValueClass fromExternalAddress:returnValue.
+	].
     ] ifFalse:[
-        returnType isCPointer ifTrue:[
-            returnType baseType isCStruct ifTrue:[
-                stClass := Smalltalk classNamed:returnType baseType name.
-                stClass notNil ifTrue:[
-                    self isConstReturnValue ifTrue:[
-                        returnValue changeClassTo:returnValueClass.
-                        ^ returnValue
-                    ].
-                    ^ stClass fromExternalAddress:returnValue.
-                ].
-            ].
-            returnType baseType isCChar ifTrue:[
-                ^ returnValue stringAt:1
-            ].
-        ].
+	returnType isCPointer ifTrue:[
+	    returnType baseType isCStruct ifTrue:[
+		stClass := Smalltalk classNamed:returnType baseType name.
+		stClass notNil ifTrue:[
+		    self isConstReturnValue ifTrue:[
+			returnValue changeClassTo:returnValueClass.
+			^ returnValue
+		    ].
+		    ^ stClass fromExternalAddress:returnValue.
+		].
+	    ].
+	    returnType baseType isCChar ifTrue:[
+		^ returnValue stringAt:1
+	    ].
+	].
     ].
 
     ^ returnValue
--- a/ExternalStructure.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/ExternalStructure.st	Fri Apr 08 07:02:36 2016 +0100
@@ -157,6 +157,12 @@
         size:(anExternalAddressOrExternalStructure size).
 ! !
 
+!ExternalStructure methodsFor:'testing'!
+
+isExternalStructure
+    ^ true
+! !
+
 !ExternalStructure class methodsFor:'documentation'!
 
 version
--- a/IdentityDictionary.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/IdentityDictionary.st	Fri Apr 08 07:02:36 2016 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Dictionary subclass:#IdentityDictionary
 	instanceVariableNames:''
 	classVariableNames:''
@@ -97,7 +99,7 @@
     [
         probe := keyArray basicAt:index.
         probe == key ifTrue:[^ index].         "<<<< == is different from inherited"
-        (self slotIsEmpty:probe) ifTrue:[^ aBlock value].
+        probe isNil ifTrue:[^ aBlock value].
 
         index == length ifTrue:[
             index := 1
@@ -110,13 +112,16 @@
 
 findKeyOrNil:key
     "Look for the key in the receiver.  
-     If it is found, return return the index of the first unused slot. 
-     Grow the receiver, if key was not found, and no unused slots were present"
+     If it is found, return the index of the first unused slot. 
+     Grow the receiver, if key was not found, and no unused slots were present
+
+     Warning: an empty slot MUST be filled by the sender - it is only to be sent
+              by at:put: / add: - like methods."
 
     |index  "{ Class:SmallInteger }"
      length "{ Class:SmallInteger }"
      startIndex probe 
-     delIndex "{ Class:SmallInteger }" |
+     delIndex "{ Class:SmallInteger }"|
 
     delIndex := 0.
 
@@ -125,8 +130,8 @@
 
     [
         probe := keyArray basicAt:index.
-        key == probe ifTrue:[^ index].
-        (self slotIsEmpty:probe) ifTrue:[
+        key == probe ifTrue:[^ index].              "<<<< == is different from inherited"   
+        probe isNil ifTrue:[
             delIndex == 0 ifTrue:[^ index].
             keyArray basicAt:delIndex put:nil.
             ^ delIndex
@@ -192,6 +197,6 @@
 !IdentityDictionary class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/IdentityDictionary.st,v 1.31 2014-03-07 22:07:13 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/IdentitySet.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/IdentitySet.st	Fri Apr 08 07:02:36 2016 +0100
@@ -11,6 +11,8 @@
 "
 "{ Package: 'stx:libbasic' }"
 
+"{ NameSpace: Smalltalk }"
+
 Set subclass:#IdentitySet
 	instanceVariableNames:''
 	classVariableNames:''
@@ -115,8 +117,8 @@
     count := 0.
     [
         probe := keyArray basicAt:index.
-        (probe notNil and:[key == probe]) ifTrue:[^ count].
-        (self slotIsEmpty:probe) ifTrue:[self error:'non existing key'].
+        probe isNil ifTrue:[self error:'non existing key'].
+        key == probe ifTrue:[^ count].
 
         index == length ifTrue:[
             index := 1.
@@ -153,7 +155,7 @@
     [
         probe := keyArray basicAt:index.
         probe == key ifTrue:[^ index].        "<<<< == is different from inherited"
-        (self slotIsEmpty:probe) ifTrue:[^ aBlock value].
+        probe isNil ifTrue:[^ aBlock value].
 
         index == length ifTrue:[
             index := 1
@@ -175,12 +177,15 @@
 findKeyOrNil:key
     "Look for the key in the receiver.  
      If it is found, return return the index of the first unused slot. 
-     Grow the receiver, if key was not found, and no unused slots were present"
+     Grow the receiver, if key was not found, and no unused slots were present
+
+     Warning: an empty slot MUST be filled by the sender - it is only to be sent
+              by at:put: / add: - like methods."
 
     |index  "{ Class:SmallInteger }"
      length "{ Class:SmallInteger }"
      startIndex probe 
-     delIndex "{ Class:SmallInteger }" |
+     delIndex "{ Class:SmallInteger }"|
 
     delIndex := 0.
 
@@ -190,7 +195,7 @@
     [
         probe := keyArray basicAt:index.
         key == probe ifTrue:[^ index].
-        (self slotIsEmpty:probe) ifTrue:[
+        probe isNil ifTrue:[
             delIndex == 0 ifTrue:[^ index].
             keyArray basicAt:delIndex put:nil.
             ^ delIndex
@@ -283,6 +288,6 @@
 !IdentitySet class methodsFor:'documentation'!
 
 version
-    ^ '$Header: /cvs/stx/stx/libbasic/IdentitySet.st,v 1.38 2014-03-07 22:06:33 stefan Exp $'
+    ^ '$Header$'
 ! !
 
--- a/Integer.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/Integer.st	Fri Apr 08 07:02:36 2016 +0100
@@ -799,6 +799,7 @@
     "Modified: 18.7.1996 / 12:26:38 / cg"
 ! !
 
+
 !Integer class methodsFor:'prime numbers'!
 
 flushPrimeCache
@@ -1174,6 +1175,7 @@
     ^ self == Integer
 ! !
 
+
 !Integer methodsFor:'Compatibility-Dolphin'!
 
 & aNumber
@@ -1439,6 +1441,7 @@
 ! !
 
 
+
 !Integer methodsFor:'bcd conversion'!
 
 decodeFromBCD
@@ -2735,7 +2738,7 @@
 hash
     "redefined to return smallInteger hashValues"
 
-    ^ self bitAnd:16r3FFFFFFF.
+    ^ self bitAnd:SmallInteger maxVal.
 
     "
         -20000000000000 hash
@@ -4852,6 +4855,7 @@
     "Created: / 09-01-2012 / 17:18:06 / cg"
 ! !
 
+
 !Integer methodsFor:'special modulo arithmetic'!
 
 add_32:anInteger
--- a/LargeInteger.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/LargeInteger.st	Fri Apr 08 07:02:36 2016 +0100
@@ -2200,31 +2200,30 @@
 hash
     "return an integer useful for hashing on large numbers"
 
-    |l h m|
-
-    h := self bitAnd:16r3FFFFFFF.
-
-    l := digitByteArray size.
-    l >= 8 ifTrue:[
-	h := h bitXor:(digitByteArray at:l).
-	h := h bitXor:((digitByteArray at:l-1) bitShift:8).
-	h := h bitXor:((digitByteArray at:l-2) bitShift:16).
-	h := h bitXor:((digitByteArray at:l-3) bitShift:22).
-	l >= 12 ifTrue:[
-	    m := l // 2.
-	    h := h bitXor:(digitByteArray at:m-1).
-	    h := h bitXor:((digitByteArray at:m) bitShift:8).
-	    h := h bitXor:((digitByteArray at:m+1) bitShift:16).
-	    h := h bitXor:((digitByteArray at:m+2) bitShift:22).
-	].
-	^ h
+    |sz h|
+
+    sz := digitByteArray size.
+    (sz <= SmallInteger maxBytes and:[self absLess:SmallInteger maxVal]) ifTrue:[
+        "I am really an unnormalized SmallInteger, answer the same hash as for the SmallInteger"
+        ^ self bitAnd:SmallInteger maxVal.
     ].
-    ^ (h bitShift:3) + l
+
+    h := digitByteArray computeXorHashFrom:1 to:8.                  "/ the low 8 bytes
+    sz > 8 ifTrue:[                                                 "/ the high 8 bytes
+        h := h bitXor:(digitByteArray computeXorHashFrom:sz-8 to:sz).
+    ].
+    ^ h
 
     "
      16r80000000 hash
+     16r-80000000 asLargeInteger hash
      16r80000008 hash
      16r8000000000008 hash
+
+     16r8000000000000000 hash
+     16r8000000000000008 hash
+     16r800000000000000000008 hash
+     16r-800000000000000000008 hash
     "
 !
 
--- a/Object.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/Object.st	Fri Apr 08 07:02:36 2016 +0100
@@ -1,3 +1,5 @@
+"{ Encoding: utf8 }"
+
 "
  COPYRIGHT (c) 1988 by Claus Gittinger
 	      All Rights Reserved
@@ -516,6 +518,7 @@
 ! !
 
 
+
 !Object methodsFor:'Compatibility-Dolphin'!
 
 stbFixup: anSTBInFiler at: newObjectIndex
@@ -9280,6 +9283,10 @@
     ^false
 !
 
+isExternalStructure
+    ^ false
+!
+
 isFileStream
     "return true, if the receiver is some kind of fileStream;
      false is returned here - the method is only redefined in FileStream."
--- a/ProjectDefinition.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/ProjectDefinition.st	Fri Apr 08 07:02:36 2016 +0100
@@ -4302,9 +4302,9 @@
                 ].
 
             putDependencyForClassBaseNameBlock := [:clsBaseName |
-                    s nextPutAll:'$(OUTDIR)'.
-                    s nextPutAll:clsBaseName.
-                    s nextPutAll:'.$(O)'.
+                    s nextPutAll:('$(OUTDIR)',clsBaseName,'.$(O)').
+                    s nextPutAll:' '.
+                    s nextPutAll:(clsBaseName,'.$(C)').
                     s nextPutAll:' '.
                     s nextPutAll:clsBaseName.
                     s nextPutAll:'.$(H)'.
@@ -4772,6 +4772,7 @@
     ^ self subProjectMakeCallsUsing:'call vcmake %1 %2'.
 ! !
 
+
 !ProjectDefinition class methodsFor:'file templates'!
 
 autopackage_default_dot_apspec
--- a/SequenceableCollection.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/SequenceableCollection.st	Fri Apr 08 07:02:36 2016 +0100
@@ -398,6 +398,7 @@
     ^ self == SequenceableCollection
 ! !
 
+
 !SequenceableCollection methodsFor:'Compatibility-Squeak'!
 
 allButFirst
@@ -2183,7 +2184,7 @@
     h := h bitAnd:16r01FFFFFF.
     h := (h bitShift:5) + (self at:mySize) hash.
     h := h bitAnd:16r01FFFFFF.
-    h := (h bitShift:5) + self size.
+    h := (h bitShift:5) + mySize.
     ^ h bitAnd:16r3FFFFFFF.
 
     "/ cg: the code below may lead to largeInteger arithmetic, which was slow...
@@ -7783,6 +7784,7 @@
     "Created: 14.2.1997 / 16:13:03 / cg"
 ! !
 
+
 !SequenceableCollection methodsFor:'searching'!
 
 detect:aBlock startingAt:startIndex
--- a/Set.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/Set.st	Fri Apr 08 07:02:36 2016 +0100
@@ -813,6 +813,7 @@
 ! !
 
 
+
 !Set methodsFor:'obsolete set operations'!
 
 + aCollection
@@ -857,9 +858,9 @@
     startIndex := index := self initialIndexForKey:key.
 
     [
-        probe := (keyArray basicAt:index).
-        (probe notNil and:[probe ~~ DeletedEntry and:[key = probe]]) ifTrue:[^ index].
-        (self slotIsEmpty:probe) ifTrue:[^ aBlock value].
+        probe := keyArray basicAt:index.
+        probe isNil ifTrue:[^ aBlock value].
+        (probe ~~ DeletedEntry and:[key = probe]) ifTrue:[^ index].
 
         index == length ifTrue:[
             index := 1
@@ -883,29 +884,34 @@
 findKeyOrNil:key
     "Look for the key in the receiver.  
      If it is found, return the index of the first unused slot. 
-     Grow the receiver, if key was not found, and no unused slots were present"
+     Grow the receiver, if key was not found, and no unused slots were present
+
+     Warning: an empty slot MUST be filled by the sender - it is only to be sent
+              by at:put: / add: - like methods."
 
     |index  "{ Class:SmallInteger }"
      length "{ Class:SmallInteger }"
      startIndex probe 
-     delIndex|
+     delIndex "{ Class:SmallInteger }"|
+
+    delIndex := 0.
 
     length := keyArray basicSize.
     startIndex := index := self initialIndexForKey:key.
 
     [
         probe := keyArray basicAt:index.
-        (probe notNil and:[probe ~~ DeletedEntry and:[key = probe]]) ifTrue:[^ index].
-        (self slotIsEmpty:probe) ifTrue:[
-            delIndex isNil ifTrue:[^ index].
+        probe isNil ifTrue:[
+            delIndex == 0 ifTrue:[^ index].
             keyArray basicAt:delIndex put:nil.
             ^ delIndex
         ].
-
         probe == DeletedEntry ifTrue:[
-            delIndex isNil ifTrue:[
+            delIndex == 0 ifTrue:[
                 delIndex := index
             ]
+        ] ifFalse:[
+            key = probe ifTrue:[^ index]
         ].
 
         index == length ifTrue:[
@@ -914,7 +920,7 @@
             index := index + 1
         ].
         index == startIndex ifTrue:[
-            delIndex notNil ifTrue:[
+            delIndex ~~ 0 ifTrue:[
                 keyArray basicAt:delIndex put:nil.
                 ^ delIndex
             ].
@@ -1086,13 +1092,6 @@
 	].
 	element := keyArray basicAt:index.
     ]
-!
-
-slotIsEmpty:aSlotValue
-    "only redefined in weak subclasses, since they treat a 0-value
-     as being empty"
-
-    ^ aSlotValue isNil
 ! !
 
 !Set methodsFor:'private-grow & shrink'!
@@ -1204,7 +1203,7 @@
     [
         probe := keyArray basicAt:index.
         (probe notNil and:[key = probe]) ifTrue:[^ count].
-        (self slotIsEmpty:probe) ifTrue:[self error:'non existing key'].
+        probe isNil ifTrue:[self error:'non existing key'].
 
         index == length ifTrue:[
             index := 1.
@@ -1240,6 +1239,7 @@
     ^ tally
 ! !
 
+
 !Set methodsFor:'searching'!
 
 findFirst:aBlock ifNone:exceptionValue
--- /dev/null	Thu Jan 01 00:00:00 1970 +0000
+++ b/SimpleExternalLibraryFunction.st	Fri Apr 08 07:02:36 2016 +0100
@@ -0,0 +1,315 @@
+"{ Package: 'stx:libbasic' }"
+
+"{ NameSpace: Smalltalk }"
+
+ExternalLibraryFunction subclass:#SimpleExternalLibraryFunction
+	instanceVariableNames:''
+	classVariableNames:''
+	poolDictionaries:''
+	category:'System-Support'
+!
+
+!SimpleExternalLibraryFunction class methodsFor:'documentation'!
+
+documentation
+"
+    instances of me are used for very simple functions, with all integer or
+    equivalent arguments.
+    These avoid the realively expensive ffi- arg setup, and jump directly to the
+    target function.
+    Can be used for a subset of all external functions and only on some machines.
+    Only for tuning; the superclass must provide a fallback for all calls
+"
+! !
+
+!SimpleExternalLibraryFunction methodsFor:'private invoking'!
+
+invokeFFIwithArguments:argumentsOrNil forCPPInstance:aReceiverOrNil
+    "the caller must have already checked, if instances of me are appropriate.
+     May only be used for up to 10 args, with INT-sized non-float, non-struct arguments,
+     and int-sized, non-float, non-struct return value.
+     Now, all I do is convert the arguments and transfer directly; without the expensive ffi..."
+
+    |argTypeSymbols returnTypeSymbol failureCode failureArgNr failureInfo returnValue stClass vtOffset
+     virtual objectiveC async unlimitedStack callTypeNumber returnValueClass argValueClass
+     oldReturnType oldArgumentTypes|
+
+    virtual := self isVirtualCPP.
+    objectiveC := self isObjectiveC.
+    (virtual "or:[self isNonVirtualCPP]") ifTrue:[
+        aReceiverOrNil isNil ifTrue:[
+            "/ must have a c++ object instance
+            self primitiveFailed.
+        ].
+
+        "/ and it must be a kind of ExternalStructure !!
+        (aReceiverOrNil isExternalStructure) ifFalse:[
+            self primitiveFailed.
+        ].
+        virtual ifTrue:[
+            vtOffset := name.
+        ].
+    ] ifFalse:[
+        objectiveC ifTrue:[
+            aReceiverOrNil isNil ifTrue:[
+                "/ must have an objective-c object instance
+                self primitiveFailed.
+            ].
+            (aReceiverOrNil isObjectiveCObject) ifFalse:[
+                self primitiveFailed
+            ]
+        ] ifFalse:[
+            aReceiverOrNil notNil ifTrue:[
+                "/ must NOT have a c++/objectiveC object instance
+                self primitiveFailed.
+            ]
+        ].
+    ].
+
+%{  /* STACK: 100000 */
+
+#define VERBOSE
+#define MAX_ARGS 10
+
+    int __numArgs, __numArgsIncludingThis;
+    static INT null = 0;
+    INT __args[MAX_ARGS+1];
+    INT retVal;
+    int i = -1;
+    int argIdx = 0;
+    INTFUNC codeAddress = (VOIDFUNC)__INST(code_);
+    int __numArgsWanted;
+
+#   define __FAIL__(fcode) \
+    { \
+        failureCode = fcode; failureArgNr = __mkSmallInteger(i+1); goto getOutOfHere; \
+    }
+
+    if (argumentsOrNil == nil) {
+        __numArgs = 0;
+    } else if (__isArray(argumentsOrNil)) {
+        __numArgs = __arraySize(argumentsOrNil);
+    } else {
+        __FAIL__(@symbol(BadArgumentVector))
+    }
+    if (__numArgs != __numArgsWanted) {
+        __FAIL__(@symbol(ArgumentCountMismatch))
+    }
+    if (__numArgs > MAX_ARGS) {
+        __FAIL__(@symbol(TooManyArguments))
+    }
+
+    /*
+     * validate the c++ object
+     */
+    if (aReceiverOrNil != nil) {
+        struct cPlusPlusInstance {
+            void **vTable;
+        };
+        struct cPlusPlusInstance *inst;
+
+        if (__isExternalAddressLike(aReceiverOrNil)) {
+            inst = (void *)(__externalAddressVal(aReceiverOrNil));
+        } else if (__isExternalBytesLike(aReceiverOrNil)) {
+            inst = (void *)(__externalBytesVal(aReceiverOrNil));
+        } else {
+            __FAIL__(@symbol(InvalidInstance))
+        }
+        __args[0] = (INT)inst;
+        __numArgsIncludingThis = __numArgs + 1;
+        argIdx = 1;
+
+        if (virtual == true) {
+            if (! __isSmallInteger(vtOffset)) {
+                __FAIL__(@symbol(InvalidVTableIndex))
+            }
+            codeAddress = inst->vTable[__intVal(vtOffset)];
+# ifdef VERBOSE
+            if (@global(Verbose) == true) {
+                printf("virtual %d codeAddress: %"_lx_"\n", __intVal(vtOffset), (INT)codeAddress);
+            }
+# endif
+        }
+    } else {
+        __numArgsIncludingThis = __numArgs;
+# ifdef VERBOSE
+        if (@global(Verbose) == true) {
+            printf("codeAddress: %"_lx_"\n", (INT)codeAddress);
+        }
+# endif
+    }
+
+    /*
+     * validate all arg types, map each to an ffi_type, and setup arg-buffers
+     */
+    for (i=0; i<__numArgs; i++, argIdx++) {
+        OBJ arg;
+
+        failureInfo = __mkSmallInteger(i+1);   /* in case there is one */
+
+        arg = __ArrayInstPtr(argumentsOrNil)->a_element[i];
+
+        if (__isSmallInteger(arg)) {
+            __args[argIdx] = __intVal(arg);
+        } else {
+           INT iv = __signedLongIntVal(arg);
+           if (iv != 0) {
+                __args[argIdx]  = iv;
+            } else {
+                unsigned INT iv = __unsignedLongIntVal(arg);
+                if (iv != 0) {
+                    __args[argIdx] = iv;
+                } else {
+                    if (__isStringLike(arg)) {
+                        __args[argIdx] = (INT)(__stringVal(arg));
+                    } else {
+                        if (__isBytes(arg)) {
+                            __args[argIdx] = (INT)(__byteArrayVal(arg));
+                            if (arg == NULL) {
+                                __args[argIdx] = (INT)0;
+                            } else {
+                                if (__isExternalAddressLike(arg)) {
+                                    __args[argIdx] = (INT)(__externalAddressVal(arg));
+                                } else {
+                                    if (__isExternalBytesLike(arg)) {
+                                        __args[argIdx] = (INT)(__externalBytesVal(arg));
+                                    } else {
+                                        __FAIL__(@symbol(InvalidArgument))
+                                    }
+                                }
+                            }
+                        }
+                    }
+                }
+            }
+        }
+    }
+    failureInfo = nil;
+
+    retVal = (*codeAddress)(__args[0], __args[1], __args[2], __args[3], __args[4], __args[5], __args[6],
+                            __args[7], __args[8], __args[9], __args[10]);
+
+# ifdef VERBOSE
+    if (@global(Verbose) == true) {
+        printf("retval is %"_ld_" (0x%"_lx_")\n", retVal, retVal);
+    }
+# endif
+
+    if ((returnTypeSymbol == @symbol(int))
+     || (returnTypeSymbol == @symbol(sint))
+     || (returnTypeSymbol == @symbol(sint8))
+     || (returnTypeSymbol == @symbol(sint16))
+     || (returnTypeSymbol == @symbol(sint32))) {
+# ifdef VERBOSE
+        if (@global(Verbose) == true) {
+            printf("return int: %x\n", retVal);
+        }
+# endif
+        RETURN ( __MKINT(retVal) );
+    }
+    if ((returnTypeSymbol == @symbol(uint))
+     || (returnTypeSymbol == @symbol(uint8))
+     || (returnTypeSymbol == @symbol(uint16))
+     || (returnTypeSymbol == @symbol(uint32))) {
+# ifdef VERBOSE
+        if (@global(Verbose) == true) {
+            printf("return uint: %x\n", retVal);
+        }
+# endif
+        RETURN ( __MKUINT(retVal) );
+    }
+    if (returnTypeSymbol == @symbol(bool)) {
+        RETURN ( retVal ? true : false );
+    }
+    if (returnTypeSymbol == @symbol(void)) {
+        RETURN ( nil );
+    }
+    if (returnTypeSymbol == @symbol(char)) {
+        RETURN ( __MKCHARACTER(retVal & 0xFF) );
+    }
+    if (returnTypeSymbol == @symbol(wchar)) {
+        RETURN ( __MKUCHARACTER(retVal & 0xFFFF) );
+    }
+
+# ifdef VERBOSE
+    if (@global(Verbose) == true) {
+        printf("return pointer: %"_lx_"\n", (INT)(retVal));
+    }
+# endif
+    if (returnTypeSymbol == @symbol(handle)) {
+        returnValue = __MKEXTERNALADDRESS(retVal);
+    } else if (returnTypeSymbol == @symbol(pointer)) {
+        returnValue = __MKEXTERNALBYTES(retVal);
+    } else if (returnTypeSymbol == @symbol(bytePointer)) {
+        returnValue = __MKEXTERNALBYTES(retVal);
+    } else if (returnTypeSymbol == @symbol(charPointer)) {
+        returnValue = __MKSTRING(retVal);
+    } else if (returnTypeSymbol == @symbol(wcharPointer)) {
+        returnValue = __MKU16STRING(retVal);
+    } else {
+        __FAIL__(@symbol(UnknownReturnType2))
+    }
+getOutOfHere: ;
+%}.
+    failureCode notNil ifTrue:[
+        (failureCode == #UnknownReturnType or:[ failureCode == #UnknownArgumentType ]) ifTrue:[
+            oldReturnType := returnType.
+            oldArgumentTypes := argumentTypes.
+            self adjustTypes.
+            ((oldReturnType ~= returnType) or:[oldArgumentTypes ~= argumentTypes]) ifTrue:[
+                thisContext restart
+            ].
+        ].
+        (failureCode == #BadArgForAsyncCall) ifTrue:[
+            ^ self tryAgainWithAsyncSafeArguments:argumentsOrNil forCPPInstance:aReceiverOrNil
+        ].
+        (failureCode == #FFINotSupported) ifTrue:[
+            self primitiveFailed:'FFI support missing in this build'.
+        ].
+
+        self primitiveFailed.   "see failureCode and failureInfo for details"
+        ^ nil
+    ].
+
+    returnType isSymbol ifTrue:[
+        returnValueClass notNil ifTrue:[
+            self isConstReturnValue ifTrue:[
+                returnValue changeClassTo:returnValueClass.
+                ^ returnValue
+            ].
+            ^ returnValueClass fromExternalAddress:returnValue.
+        ].
+    ] ifFalse:[
+        returnType isCPointer ifTrue:[
+            returnType baseType isCStruct ifTrue:[
+                stClass := Smalltalk classNamed:returnType baseType name.
+                stClass notNil ifTrue:[
+                    self isConstReturnValue ifTrue:[
+                        returnValue changeClassTo:returnValueClass.
+                        ^ returnValue
+                    ].
+                    ^ stClass fromExternalAddress:returnValue.
+                ].
+            ].
+            returnType baseType isCChar ifTrue:[
+                ^ returnValue stringAt:1
+            ].
+        ].
+    ].
+
+    ^ returnValue
+
+    "Created: / 01-08-2006 / 13:56:23 / cg"
+    "Modified: / 31-03-2016 / 00:03:03 / cg"
+! !
+
+!SimpleExternalLibraryFunction class methodsFor:'documentation'!
+
+version
+    ^ '$Header$'
+!
+
+version_CVS
+    ^ '$Header$'
+! !
+
--- a/UninterpretedBytes.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/UninterpretedBytes.st	Fri Apr 08 07:02:36 2016 +0100
@@ -467,7 +467,6 @@
     "Modified: / 5.3.1998 / 14:56:22 / stefan"
 ! !
 
-
 !UninterpretedBytes methodsFor:'Compatibility'!
 
 doubleWordAt:index
@@ -4235,6 +4234,25 @@
      #[1 2 3 4 1 2 3 4] computeXorHashFrom:1 to:8.
      #[1 2 3 4 5 6 7 8] computeXorHashFrom:2 to:8.
      #[2 3 4 5 6 7 8] computeXorHashFrom:1 to:7.
+     #[2 3 4 5 6 7 8] computeXorHashFrom:1 to:8.
+    "
+!
+
+hash
+    |sz|
+
+    sz := self size.
+    sz <= 32 ifTrue:[
+        ^ self computeXorHashFrom:1 to:sz.
+    ].
+    ^ (sz bitXor:(self computeXorHashFrom:1 to:16)) bitXor:(self computeXorHashFrom:sz-16 to:sz)   
+
+    "
+        #[1 2 3 4] hash
+        #[1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4
+          1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 ] hash
+        #[1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4
+          1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1 2 3 4 1] hash
     "
 ! !
 
--- a/WeakArray.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/WeakArray.st	Fri Apr 08 07:02:36 2016 +0100
@@ -1,5 +1,3 @@
-"{ Encoding: utf8 }"
-
 "
  COPYRIGHT (c) 1991 by Claus Gittinger
 	      All Rights Reserved
@@ -43,7 +41,7 @@
     WeakArrays can be used to trace disposal of objects; in contrast to other
     objects, references by WeakArrays will NOT keep an object from being
     garbage collected.
-    Instead, whenever an object kept in a WeakArray dies, its entry is zeroed,
+    Instead, whenever an object kept in a WeakArray dies, its entry is set to a SmallInteger,
     and the WeakArray is informed by the storage manager. The WeakArray itself
     then informs possible dependents via the dependency mechanism.
 
@@ -52,7 +50,7 @@
     file when disposed (otherwise you could run out of OS filedescriptors).
     This can be done by keeping the FileStream objects in a weakArray, and
     keep a parallel array of filedescriptors. Whenever a fileStream is
-    freed, search both arrays for an index where the stream is zero, but the
+    freed, search both arrays for an index where the stream is set to a SmallInteger, but the
     filedescriptor is non-nil. Then close that file, and nil the filedescriptor
     entry. Notice, that there is a class (Registry) which does exactly this in
     a more programmer friendly way.
@@ -76,18 +74,18 @@
     A weakArray notifies its dependents via normal dependency notfications.
 
     [hint:]
-	WeakArray handling adds small some overhead to the VM
-	(each weakarray is scanned after each GC).
-	It is uncertain, if the current mechanism works well
-	with (say) ten-thousands of weakArrays.
-	We had the system running with >2000 weakArrays, some being quite
-	big for a while and had a few percent of added gc time.
-	The system as delivered creates between 50 and 100 weakArrays,
-	but with many dependents, this number may grow.
-	If you need the dependency mechanism on a huge number of objects,
-	consider adding a (non-weak) dependents field to your class
-	- take the implementation of Model as a guide (or subclass them
-	from Model).
+        WeakArray handling adds small some overhead to the VM
+        (each weakarray is scanned after each GC).
+        It is uncertain, if the current mechanism works well
+        with (say) ten-thousands of weakArrays.
+        We had the system running with >2000 weakArrays, some being quite
+        big for a while and had a few percent of added gc time.
+        The system as delivered creates between 50 and 100 weakArrays,
+        but with many dependents, this number may grow.
+        If you need the dependency mechanism on a huge number of objects,
+        consider adding a (non-weak) dependents field to your class
+        - take the implementation of Model as a guide (or subclass them
+        from Model).
 
     As a possible option, we could perform the weakArray scanning only in
     the oldSpace reclamation code - this would remove most of the overhead,
@@ -96,27 +94,27 @@
 
     [instance variables:]
 
-	dependents                  get informed via #change notifiction
-				    that the weakArray has lost pointers.
-				    Having the dependents here is an optimization.
+        dependents                  get informed via #change notifiction
+                                    that the weakArray has lost pointers.
+                                    Having the dependents here is an optimization.
 
     [class variables:]
 
-	RegistrationFailedSignal    raised if a weakArray cannot be
-				    registered by the VM. This only happens,
-				    if the VM has to resize its internal tables
-				    and is running out of malloc-memory.
+        RegistrationFailedSignal    raised if a weakArray cannot be
+                                    registered by the VM. This only happens,
+                                    if the VM has to resize its internal tables
+                                    and is running out of malloc-memory.
 
     [memory requirements:]
-	OBJ-HEADER + (size * ptr-size) + ptr-size
-		   + sizeof(dependents-collection)
+        OBJ-HEADER + (size * ptr-size) + ptr-size
+                   + sizeof(dependents-collection)
 
     [author:]
-	Claus Gittinger
+        Claus Gittinger
 
     [See also:]
-	Array WeakIdentitySet WeakIdentityDictionary Registry
-	Model
+        Array WeakIdentitySet WeakIdentityDictionary Registry
+        Model
 "
 ! !
 
--- a/WeakValueDictionary.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/WeakValueDictionary.st	Fri Apr 08 07:02:36 2016 +0100
@@ -77,7 +77,7 @@
     ^ ret
 !
 
-at:key ifAbsentPut:anObject
+at:key ifAbsentPut:replacementBlock
     "return the element indexed by aKey if present,
      if not present, store the result of evaluating valueBlock
      under aKey and return it.
@@ -85,14 +85,26 @@
      Redefined to block interrupts, to avoid trouble when dependencies
      are added within interrupting high prio processes.
      WARNING: do not add elements while iterating over the receiver.
-	      Iterate over a copy to do this."
+              Iterate over a copy to do this."
 
-    |ret|
+    |val|
 
-    [
-	ret := super at:key ifAbsentPut:anObject.
-    ] valueUninterruptably.
-    ^ ret
+    OperatingSystem blockInterrupts ifTrue:[
+        "/ already blocked
+        val := super at:key ifAbsentPut:replacementBlock.
+    ] ifFalse:[
+        [
+            val := super at:key ifAbsentPut:replacementBlock.
+        ] ensure:[
+            OperatingSystem unblockInterrupts.
+        ].
+    ].
+
+    val class == SmallInteger ifTrue:[
+        self error:'WeakValueDictionary: invalid value'.
+    ].
+
+    ^ val
 !
 
 at:key put:anObject
@@ -101,16 +113,26 @@
      Redefined to block interrupts, to avoid trouble when dependencies
      are added within interrupting high prio processes."
 
-    |ret|
+    |val|
+
+    anObject class == SmallInteger ifTrue:[
+        self error:'WeakValueDictionary: invalid value'.
+    ].
+
+    (OperatingSystem blockInterrupts) ifTrue:[
+        "/ already blocked
+        ^ super at:key put:anObject.
+    ].
 
     [
-	ret := super at:key put:anObject.
-    ] valueUninterruptably.
-    ^ ret
+        val := super at:key put:anObject.
+    ] ensure:[
+        OperatingSystem unblockInterrupts.
+    ].
+    ^ val
 
     "Modified: 6.5.1996 / 12:22:26 / stefan"
-    "Created: 6.5.1996 / 14:47:37 / stefan"
-    "Modified: 20.10.1996 / 14:05:04 / cg"
+    "Modified: 29.1.1997 / 15:08:45 / cg"
 !
 
 removeKey:aKey ifAbsent:aBlock
@@ -204,10 +226,6 @@
     super possiblyShrink
 !
 
-slotIsEmpty:probe
-    ^ probe isNil or:[probe == 0 "collected"]
-!
-
 valueContainerOfSize:n
     "return a container for values of size n.
      use WeakArrays here."
--- a/WeakValueIdentityDictionary.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/WeakValueIdentityDictionary.st	Fri Apr 08 07:02:36 2016 +0100
@@ -178,10 +178,6 @@
 
 !WeakValueIdentityDictionary methodsFor:'private'!
 
-slotIsEmpty:probe
-    ^ probe isNil or:[probe == 0 "collected"]
-!
-
 valueContainerOfSize:n
     "return a container for values of size n.
      use WeakArrays here."
@@ -204,14 +200,14 @@
     |val|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-	"/ already blocked
-	^ super includes:anObject.
+        "/ already blocked
+        ^ super includes:anObject.
     ].
 
     [
-	val := super includes:anObject.
-    ] valueNowOrOnUnwindDo:[
-	OperatingSystem unblockInterrupts.
+        val := super includes:anObject.
+    ] ensure:[
+        OperatingSystem unblockInterrupts.
     ].
     ^ val
 
@@ -227,14 +223,14 @@
     |val|
 
     (OperatingSystem blockInterrupts) ifTrue:[
-	"/ already blocked
-	^ super includesKey:key.
+        "/ already blocked
+        ^ super includesKey:key.
     ].
 
     [
-	val := super includesKey:key.
-    ] valueNowOrOnUnwindDo:[
-	OperatingSystem unblockInterrupts.
+        val := super includesKey:key.
+    ] ensure:[
+        OperatingSystem unblockInterrupts.
     ].
     ^ val
 
@@ -253,6 +249,10 @@
 
 version
     ^ '$Header$'
+!
+
+version_CVS
+    ^ '$Header$'
 ! !
 
 
--- a/stx_libbasic.st	Sun Apr 03 07:04:52 2016 +0200
+++ b/stx_libbasic.st	Fri Apr 08 07:02:36 2016 +0100
@@ -385,6 +385,7 @@
         SameForAllNotification
         SemaphoreSet
         SignalSet
+        SimpleExternalLibraryFunction
         SnapshotError
         SortedCollection
         StringCollection