ExternalLibraryFunction.st
changeset 10025 053904a63549
parent 9981 d36bdd9dbab6
child 10213 31717eee6fb2
equal deleted inserted replaced
10024:a9a71c271bd9 10025:053904a63549
    98 
    98 
    99 !ExternalLibraryFunction class methodsFor:'instance creation'!
    99 !ExternalLibraryFunction class methodsFor:'instance creation'!
   100 
   100 
   101 name:functionName module:moduleName returnType:returnType argumentTypes:argTypes
   101 name:functionName module:moduleName returnType:returnType argumentTypes:argTypes
   102     ^ self new
   102     ^ self new
   103         name:functionName module:moduleName 
   103 	name:functionName module:moduleName
   104         returnType:returnType argumentTypes:argTypes
   104 	returnType:returnType argumentTypes:argTypes
   105 
   105 
   106     "Created: / 01-08-2006 / 15:19:08 / cg"
   106     "Created: / 01-08-2006 / 15:19:08 / cg"
   107 ! !
   107 ! !
   108 
   108 
   109 !ExternalLibraryFunction class methodsFor:'class initialization'!
   109 !ExternalLibraryFunction class methodsFor:'class initialization'!
   110 
   110 
   111 initialize
   111 initialize
   112     FLAG_VIRTUAL := 16r100.          "/ a virtual c++ call
   112     "using inline access to corresponding c--defines to avoid duplicate places of knowledge"
   113     FLAG_NONVIRTUAL := 16r200.       "/ a non-virtual c++ call
   113     FLAG_VIRTUAL := %{ __MKSMALLINT(__EXTL_FLAG_VIRTUAL) %}.                "/ a virtual c++ call
   114     FLAG_UNLIMITEDSTACK := 16r400.   "/ unlimitedstack under unix
   114     FLAG_NONVIRTUAL := %{ __MKSMALLINT(__EXTL_FLAG_NONVIRTUAL) %}.          "/ a non-virtual c++ call
   115     FLAG_ASYNC := 16r800.            "/ async under win32
   115     FLAG_UNLIMITEDSTACK := %{ __MKSMALLINT(__EXTL_FLAG_UNLIMITEDSTACK) %}.  "/ unlimitedstack under unix
   116     FLAG_RETVAL_IS_CONST := 16r1000. "/ return value is not to be registered for finalization
   116     FLAG_ASYNC := %{ __MKSMALLINT(__EXTL_FLAG_ASYNC) %}.                    "/ async under win32
   117 
   117     FLAG_RETVAL_IS_CONST := %{ __MKSMALLINT(__EXTL_FLAG_RETVAL_IS_CONST) %}."/ return value is not to be registered for finalization
   118     CALLTYPE_API := 1.               "/ WINAPI-call (win32 only)
   118 
   119     CALLTYPE_C := 2.                 "/ regular C-call (the default)
   119     CALLTYPE_API := %{ __MKSMALLINT(__EXTL_CALLTYPE_API) %}.                "/ WINAPI-call (win32 only)
   120     CALLTYPE_V8 := 3.                "/ v8 call (sparc only)
   120     CALLTYPE_C := %{ __MKSMALLINT(__EXTL_CALLTYPE_C) %}.                    "/ regular C-call (the default)
   121     CALLTYPE_V9 := 4.                "/ v9 call (sparc only)
   121     CALLTYPE_V8 := %{ __MKSMALLINT(__EXTL_CALLTYPE_V8) %}.                  "/ v8 call (sparc only)
   122     CALLTYPE_UNIX64 := 5.            "/ unix64 call (alpha only)
   122     CALLTYPE_V9 := %{ __MKSMALLINT(__EXTL_CALLTYPE_V9) %}.                  "/ v9 call (sparc only)
   123 
   123     CALLTYPE_UNIX64 := %{ __MKSMALLINT(__EXTL_CALLTYPE_UNIX64) %}.          "/ unix64 call (alpha only)
   124     CALLTYPE_MASK := 16rFF.
   124 
   125 
   125     CALLTYPE_MASK := %{ __MKSMALLINT(__EXTL_CALLTYPE_MASK) %}.
   126     "Modified: / 01-08-2006 / 15:09:36 / cg"
   126 
       
   127     "
       
   128      self initialize
       
   129     "
       
   130 
       
   131     "Modified: / 03-10-2006 / 21:27:47 / cg"
   127 ! !
   132 ! !
   128 
   133 
   129 !ExternalLibraryFunction class methodsFor:'constants'!
   134 !ExternalLibraryFunction class methodsFor:'constants'!
   130 
   135 
   131 callTypeAPI
   136 callTypeAPI
   202 
   207 
   203     "Modified: / 01-08-2006 / 15:14:02 / cg"
   208     "Modified: / 01-08-2006 / 15:14:02 / cg"
   204 !
   209 !
   205 
   210 
   206 beConstReturnValue
   211 beConstReturnValue
   207     "specify that a pointer return value is not to be finalized 
   212     "specify that a pointer return value is not to be finalized
   208      (i.e. points to static data or data which is freed by c)"
   213      (i.e. points to static data or data which is freed by c)"
   209 
   214 
   210     flags := (flags ? 0) bitOr: FLAG_RETVAL_IS_CONST.
   215     flags := (flags ? 0) bitOr: FLAG_RETVAL_IS_CONST.
   211 
   216 
   212     "Created: / 01-08-2006 / 13:56:48 / cg"
   217     "Created: / 01-08-2006 / 13:56:48 / cg"
   271 
   276 
   272     "Created: / 01-08-2006 / 15:21:23 / cg"
   277     "Created: / 01-08-2006 / 15:21:23 / cg"
   273 !
   278 !
   274 
   279 
   275 isConstReturnValue
   280 isConstReturnValue
   276     "is the pointer return value not to be finalized 
   281     "is the pointer return value not to be finalized
   277      (i.e. points to static data or data which is freed by c)"
   282      (i.e. points to static data or data which is freed by c)"
   278 
   283 
   279     ^ (flags ? 0) bitTest: FLAG_RETVAL_IS_CONST.
   284     ^ (flags ? 0) bitTest: FLAG_RETVAL_IS_CONST.
   280 
   285 
   281     "Created: / 01-08-2006 / 13:56:48 / cg"
   286     "Created: / 01-08-2006 / 13:56:48 / cg"
   316     ^ self invokeFFIWithArguments:#()
   321     ^ self invokeFFIWithArguments:#()
   317 !
   322 !
   318 
   323 
   319 invokeCPPVirtualOn:anInstance
   324 invokeCPPVirtualOn:anInstance
   320     self hasCode ifFalse:[
   325     self hasCode ifFalse:[
   321         self prepareInvoke.
   326 	self prepareInvoke.
   322     ].
   327     ].
   323     ^ self invokeCPPVirtualFFIOn:anInstance withArguments:#()
   328     ^ self invokeCPPVirtualFFIOn:anInstance withArguments:#()
   324 !
   329 !
   325 
   330 
   326 invokeCPPVirtualOn:instance with:arg
   331 invokeCPPVirtualOn:instance with:arg
   327     self hasCode ifFalse:[
   332     self hasCode ifFalse:[
   328         self prepareInvoke.
   333 	self prepareInvoke.
   329     ].
   334     ].
   330     ^ self invokeCPPVirtualFFIOn:instance withArguments:(Array with:arg)
   335     ^ self invokeCPPVirtualFFIOn:instance withArguments:(Array with:arg)
   331 !
   336 !
   332 
   337 
   333 invokeCPPVirtualOn:instance with:arg1 with:arg2
   338 invokeCPPVirtualOn:instance with:arg1 with:arg2
   334     self hasCode ifFalse:[
   339     self hasCode ifFalse:[
   335         self prepareInvoke.
   340 	self prepareInvoke.
   336     ].
   341     ].
   337     ^ self invokeCPPVirtualFFIOn:instance withArguments:(Array with:arg1 with:arg2)
   342     ^ self invokeCPPVirtualFFIOn:instance withArguments:(Array with:arg1 with:arg2)
   338 !
   343 !
   339 
   344 
   340 invokeCPPVirtualOn:instance with:arg1 with:arg2 with:arg3
   345 invokeCPPVirtualOn:instance with:arg1 with:arg2 with:arg3
   341     self hasCode ifFalse:[
   346     self hasCode ifFalse:[
   342         self prepareInvoke.
   347 	self prepareInvoke.
   343     ].
   348     ].
   344     ^ self invokeCPPVirtualFFIOn:instance withArguments:(Array with:arg1 with:arg2 with:arg3)
   349     ^ self invokeCPPVirtualFFIOn:instance withArguments:(Array with:arg1 with:arg2 with:arg3)
   345 !
   350 !
   346 
   351 
   347 invokeCPPVirtualOn:instance with:arg1 with:arg2 with:arg3 with:arg4
   352 invokeCPPVirtualOn:instance with:arg1 with:arg2 with:arg3 with:arg4
   348     self hasCode ifFalse:[
   353     self hasCode ifFalse:[
   349         self prepareInvoke.
   354 	self prepareInvoke.
   350     ].
   355     ].
   351     ^ self invokeCPPVirtualFFIOn:instance withArguments:(Array with:arg1 with:arg2 with:arg3 with:arg4)
   356     ^ self invokeCPPVirtualFFIOn:instance withArguments:(Array with:arg1 with:arg2 with:arg3 with:arg4)
   352 !
   357 !
   353 
   358 
   354 invokeWith:arg
   359 invokeWith:arg
   379     ^ self invokeFFIWithArguments:(Array with:arg1 with:arg2 with:arg3 with:arg4)
   384     ^ self invokeFFIWithArguments:(Array with:arg1 with:arg2 with:arg3 with:arg4)
   380 !
   385 !
   381 
   386 
   382 invokeWithArguments:argArray
   387 invokeWithArguments:argArray
   383     self hasCode ifFalse:[
   388     self hasCode ifFalse:[
   384         self prepareInvoke.
   389 	self prepareInvoke.
   385     ].
   390     ].
   386     ^ self invokeFFIwithArguments:argArray forCPPInstance:nil
   391     ^ self invokeFFIwithArguments:argArray forCPPInstance:nil
   387 
   392 
   388     "Modified: / 01-08-2006 / 16:04:08 / cg"
   393     "Modified: / 01-08-2006 / 16:04:08 / cg"
   389 ! !
   394 ! !
   391 !ExternalLibraryFunction methodsFor:'printing'!
   396 !ExternalLibraryFunction methodsFor:'printing'!
   392 
   397 
   393 printOn:aStream
   398 printOn:aStream
   394     aStream nextPutAll:'<'.
   399     aStream nextPutAll:'<'.
   395     self isCallTypeAPI ifTrue:[
   400     self isCallTypeAPI ifTrue:[
   396         'API:' printOn:aStream.
   401 	'API:' printOn:aStream.
   397     ] ifFalse:[
   402     ] ifFalse:[
   398         'C:' printOn:aStream.
   403 	'C:' printOn:aStream.
   399     ].
   404     ].
   400     aStream nextPutAll:' '.
   405     aStream nextPutAll:' '.
   401     name printOn:aStream.
   406     name printOn:aStream.
   402     moduleName notNil ifTrue:[
   407     moduleName notNil ifTrue:[
   403         aStream nextPutAll:' module:'.
   408 	aStream nextPutAll:' module:'.
   404         moduleName printOn:aStream.
   409 	moduleName printOn:aStream.
   405     ].
   410     ].
   406     aStream nextPutAll:'>'.
   411     aStream nextPutAll:'>'.
   407 
   412 
   408     "Modified: / 01-08-2006 / 15:21:42 / cg"
   413     "Modified: / 01-08-2006 / 15:21:42 / cg"
   409 ! !
   414 ! !
   415      I.e. retrieve the module handle and the code pointer."
   420      I.e. retrieve the module handle and the code pointer."
   416 
   421 
   417     |handle moduleNameUsed functionName|
   422     |handle moduleNameUsed functionName|
   418 
   423 
   419     (moduleNameUsed := moduleName) isNil ifTrue:[
   424     (moduleNameUsed := moduleName) isNil ifTrue:[
   420         owningClass isNil ifTrue:[
   425 	owningClass isNil ifTrue:[
   421             self error:'Missing moduleName'.
   426 	    self error:'Missing moduleName'.
   422         ].
   427 	].
   423         moduleNameUsed := owningClass theNonMetaclass libraryName asSymbol.
   428 	moduleNameUsed := owningClass theNonMetaclass libraryName asSymbol.
   424     ].
   429     ].
   425     moduleHandle isNil ifTrue:[
   430     moduleHandle isNil ifTrue:[
   426         handle := ObjectFileLoader loadDynamicObject:(moduleNameUsed asString).
   431 	handle := ObjectFileLoader loadDynamicObject:(moduleNameUsed asString).
   427         handle isNil ifTrue:[
   432 	handle isNil ifTrue:[
   428             handle := ObjectFileLoader 
   433 	    handle := ObjectFileLoader
   429                         loadDynamicObject:(Filename currentDirectory construct:moduleNameUsed) pathName.
   434 			loadDynamicObject:(Filename currentDirectory construct:moduleNameUsed) pathName.
   430             handle isNil ifTrue:[
   435 	    handle isNil ifTrue:[
   431                 self error:'Cannot load module: ', moduleNameUsed.
   436 		self error:'Cannot load module: ', moduleNameUsed.
   432             ].
   437 	    ].
   433         ].
   438 	].
   434         moduleHandle := handle.
   439 	moduleHandle := handle.
   435     ].
   440     ].
   436     name isNumber ifFalse:[
   441     name isNumber ifFalse:[
   437         functionName := name.
   442 	functionName := name.
   438         (moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
   443 	(moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
   439             functionName := ('_', functionName) asSymbol.
   444 	    functionName := ('_', functionName) asSymbol.
   440 
   445 
   441             (moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
   446 	    (moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
   442                 moduleHandle := nil.    
   447 		moduleHandle := nil.
   443                 self error:'Missing function: ', name, ' in module: ', moduleNameUsed.
   448 		self error:'Missing function: ', name, ' in module: ', moduleNameUsed.
   444             ].
   449 	    ].
   445         ].
   450 	].
   446     ].
   451     ].
   447 
   452 
   448     "Modified: / 01-08-2006 / 16:24:14 / cg"
   453     "Modified: / 01-08-2006 / 16:24:14 / cg"
   449 !
   454 !
   450 
   455 
   451 prepareInvoke
   456 prepareInvoke
   452     self hasCode ifFalse:[
   457     moduleHandle isNil ifTrue:[
   453         moduleHandle isNil ifTrue:[
   458 	self linkToModule.
   454             self linkToModule.
   459 	self adjustTypes.
   455         ].
   460     ].
   456     ].
   461 !
       
   462 
       
   463 adjustTypes
       
   464     argumentTypes notNil ifTrue:[
       
   465 	argumentTypes := argumentTypes collect:[:argType | self ffiTypeSymbolForType:argType].
       
   466     ].
       
   467     returnType := self ffiTypeSymbolForType:returnType.
   457 ! !
   468 ! !
   458 
   469 
   459 !ExternalLibraryFunction methodsFor:'private-accessing'!
   470 !ExternalLibraryFunction methodsFor:'private-accessing'!
   460 
   471 
   461 ffiTypeSymbolForType:aType
   472 ffiTypeSymbolForType:aType
       
   473     "map type to one of the ffi-supported ones:
       
   474 	sint8, sint16, sint32, sint64
       
   475 	uint8, uint16, uint32, uint64
       
   476 	bool void handle
       
   477     "
       
   478 
   462     |t|
   479     |t|
   463 
   480 
   464     "/ kludge for those who do not have the CType package...
   481     aType == #sint8           ifTrue:[^ aType ].
   465     t := aType.
   482     aType == #sint16          ifTrue:[^ aType ].
   466     t isSymbol ifTrue:[
   483     aType == #sint32          ifTrue:[^ aType ].
   467         t == #int8 ifTrue:[^ #sint8 ].
   484     aType == #sint64          ifTrue:[^ aType ].
   468         t == #int16 ifTrue:[^ #sint16 ].
   485     aType == #uint8           ifTrue:[^ aType ].
   469         t == #int32 ifTrue:[^ #sint32 ].
   486     aType == #uint16          ifTrue:[^ aType ].
   470         t == #int64 ifTrue:[^ #sint64 ].
   487     aType == #uint32          ifTrue:[^ aType ].
   471         t == #bool ifTrue:[^ #boolean ].
   488     aType == #uint64          ifTrue:[^ aType ].
   472         t == #voidPointer ifTrue:[^ #handle ].
   489     aType == #double          ifTrue:[^ aType ].
   473         ^ t.
   490     aType == #float           ifTrue:[^ aType ].
   474     ].
   491     aType == #char            ifTrue:[^ aType ].
   475 
   492     aType == #void            ifTrue:[^ aType ].
   476     aType isString ifFalse:[ 
   493     aType == #bool            ifTrue:[^ aType ].
   477         CType isNil ifTrue:[
   494     aType == #pointer         ifTrue:[^ aType ].
   478             self error:'unknown type'.
   495 
   479         ].
   496     aType == #int8            ifTrue:[^ #sint8 ].
   480         t := aType typeSymbol.
   497     aType == #int16           ifTrue:[^ #sint16 ].
   481     ].
   498     aType == #int32           ifTrue:[^ #sint32 ].
   482     aType isString ifTrue:[ 
   499     aType == #int64           ifTrue:[^ #sint64 ].
   483         self halt:'oops'
   500     aType == #voidPointer     ifTrue:[^ #pointer ].
   484     ].
   501 
   485     t isSymbol ifFalse:[
   502     aType == #short           ifTrue:[^ #int16 ].
   486         self error:'unknown type'.
   503     aType == #long            ifTrue:[^ #int32 ].     "/ TODO - care for 64bit machines
   487     ].
   504     aType == #int             ifTrue:[^ #int32 ].     "/ TODO - care for 64bit machines
   488 
   505     aType == #ushort          ifTrue:[^ #uint16 ].
   489     ^ t
   506     aType == #unsignedShort   ifTrue:[^ #uint16 ].
       
   507     aType == #ulong           ifTrue:[^ #uint32 ].    "/ TODO - care for 64bit machines
       
   508     aType == #unsignedLong    ifTrue:[^ #uint32 ].    "/ TODO - care for 64bit machines
       
   509     aType == #uchar           ifTrue:[^ #uint8 ].
       
   510     aType == #unsignedChar    ifTrue:[^ #uint8 ].
       
   511     aType == #byte            ifTrue:[^ #uint8 ].
       
   512     aType == #dword           ifTrue:[^ #uint32 ].
       
   513     aType == #sdword          ifTrue:[^ #int32 ].
       
   514     aType == #word            ifTrue:[^ #uint16 ].
       
   515     aType == #sword           ifTrue:[^ #int16 ].
       
   516     aType == #handle          ifTrue:[^ #pointer ].
       
   517     aType == #lpstr           ifTrue:[^ #charPointer ].
       
   518     aType == #hresult         ifTrue:[^ #uint32 ].
       
   519     aType == #boolean         ifTrue:[^ #bool ].
       
   520     aType == #ulongReturn     ifTrue:[^ #uint32 ].    "/ TODO - care for 64bit machines
       
   521     aType == #none            ifTrue:[^ #void ].
       
   522     aType == #struct          ifTrue:[^ #pointer ].
       
   523     aType == #structIn        ifTrue:[^ #pointer ].
       
   524     aType == #structOut       ifTrue:[^ #pointer ].
       
   525 
       
   526     (aType isString or:[aType isSymbol]) ifFalse:[
       
   527 	CType isNil ifTrue:[
       
   528 	    self error:'unknown type'.
       
   529 	].
       
   530 	^ aType typeSymbol.
       
   531     ].
       
   532 
       
   533     ^ aType
   490 !
   534 !
   491 
   535 
   492 name:functionNameOrVirtualIndex module:aModuleName returnType:aReturnType argumentTypes:argTypes
   536 name:functionNameOrVirtualIndex module:aModuleName returnType:aReturnType argumentTypes:argTypes
   493     name := functionNameOrVirtualIndex.
   537     name := functionNameOrVirtualIndex.
   494     functionNameOrVirtualIndex isNumber ifTrue:[
   538     functionNameOrVirtualIndex isNumber ifTrue:[
   495         self beVirtualCPP.
   539 	self beVirtualCPP.
   496     ].
   540     ].
   497     moduleName := aModuleName.
   541     moduleName := aModuleName.
   498     returnType := aReturnType.
   542     returnType := aReturnType.
   499     argumentTypes := argTypes.
   543     argumentTypes := argTypes.
   500 
   544 
   520     ^ self invokeFFIwithArguments:arguments forCPPInstance:nil
   564     ^ self invokeFFIwithArguments:arguments forCPPInstance:nil
   521 
   565 
   522     "Modified: / 01-08-2006 / 13:55:35 / cg"
   566     "Modified: / 01-08-2006 / 13:55:35 / cg"
   523 !
   567 !
   524 
   568 
   525 invokeFFIwithArguments:arguments forCPPInstance:aCPlusPlusObjectOrNil 
   569 invokeFFIwithArguments:arguments forCPPInstance:aCPlusPlusObjectOrNil
   526     |argTypeSymbols returnTypeSymbol failureCode failureInfo returnValue stClass vtOffset 
   570     |argTypeSymbols returnTypeSymbol failureCode failureInfo returnValue stClass vtOffset
   527      virtual async unlimitedStack callTypeNumber returnValueClass argValueClass|
   571      virtual async unlimitedStack callTypeNumber returnValueClass argValueClass|
   528 
   572 
   529     argumentTypes notNil ifTrue:[
   573     argTypeSymbols := argumentTypes.
   530         argTypeSymbols := argumentTypes collect:[:argType | self ffiTypeSymbolForType:argType].
   574     returnTypeSymbol := returnType.
   531     ].
   575 
   532     returnTypeSymbol := self ffiTypeSymbolForType:returnType.
   576     virtual := self isVirtualCPP.
   533 
       
   534     virtual := self isVirtualCPP.    
       
   535     (virtual "or:[self isNonVirtualCPP]") ifTrue:[
   577     (virtual "or:[self isNonVirtualCPP]") ifTrue:[
   536         aCPlusPlusObjectOrNil isNil ifTrue:[
   578 	aCPlusPlusObjectOrNil isNil ifTrue:[
   537             "/ must have a c++ object instance
   579 	    "/ must have a c++ object instance
   538             self primitiveFailed.
   580 	    self primitiveFailed.
   539         ].
   581 	].
   540 
   582 
   541         "/ and it must be a kind of ExternalStructure !!
   583 	"/ and it must be a kind of ExternalStructure !!
   542         (aCPlusPlusObjectOrNil isKindOf:ExternalStructure) ifFalse:[
   584 	(aCPlusPlusObjectOrNil isKindOf:ExternalStructure) ifFalse:[
   543             self primitiveFailed.
   585 	    self primitiveFailed.
   544         ].
   586 	].
   545         virtual ifTrue:[
   587 	virtual ifTrue:[
   546             vtOffset := name.
   588 	    vtOffset := name.
   547             (vtOffset between:0 and:10000) ifFalse:[
   589 	    (vtOffset between:0 and:10000) ifFalse:[
   548                 self primitiveFailed.
   590 		self primitiveFailed.
   549             ]
   591 	    ]
   550         ].
   592 	].
   551     ] ifFalse:[
   593     ] ifFalse:[
   552         aCPlusPlusObjectOrNil notNil ifTrue:[
   594 	aCPlusPlusObjectOrNil notNil ifTrue:[
   553             "/ must NOT have a c++ object instance
   595 	    "/ must NOT have a c++ object instance
   554             self primitiveFailed.
   596 	    self primitiveFailed.
   555         ].
   597 	].
   556     ].
   598     ].
   557     async := self isAsync.
   599     async := self isAsync.
   558     unlimitedStack := self isUnlimitedStack.
   600     unlimitedStack := self isUnlimitedStack.
   559     callTypeNumber := self callTypeNumber.
   601     callTypeNumber := self callTypeNumber.
   560 
   602 
   561 %{  /* STACK: 100000 */
   603 %{  /* STACK: 100000 */
   562 #ifdef HAVE_FFI   
   604 #ifdef HAVE_FFI
   563     ffi_cif __cif;
   605     ffi_cif __cif;
   564     ffi_type *__argTypesIncludingThis[MAX_ARGS+1];
   606     ffi_type *__argTypesIncludingThis[MAX_ARGS+1];
   565     ffi_type **__argTypes = __argTypesIncludingThis;
   607     ffi_type **__argTypes = __argTypesIncludingThis;
   566     ffi_type *__returnType = NULL;
   608     ffi_type *__returnType = NULL;
   567     union u {
   609     union u {
   568         int iVal;
   610 	int iVal;
   569         float fVal;
   611 	float fVal;
   570         double dVal;
   612 	double dVal;
   571         void *pointerVal;
   613 	void *pointerVal;
   572     };
   614     };
   573     union u __argValuesIncludingThis[MAX_ARGS+1];
   615     union u __argValuesIncludingThis[MAX_ARGS+1];
   574     union u *__argValues = __argValuesIncludingThis;
   616     union u *__argValues = __argValuesIncludingThis;
   575     union u __returnValue;
   617     union u __returnValue;
   576     void *__argValuePointersIncludingThis[MAX_ARGS+1];
   618     void *__argValuePointersIncludingThis[MAX_ARGS+1];
   581     int i;
   623     int i;
   582     ffi_abi __callType = FFI_DEFAULT_ABI;
   624     ffi_abi __callType = FFI_DEFAULT_ABI;
   583     VOIDFUNC codeAddress = (VOIDFUNC)__INST(code_);
   625     VOIDFUNC codeAddress = (VOIDFUNC)__INST(code_);
   584 
   626 
   585     if (arguments == nil) {
   627     if (arguments == nil) {
   586         __numArgs = 0;
   628 	__numArgs = 0;
   587         if (argTypeSymbols != nil) {
   629 	if (argTypeSymbols != nil) {
   588             if (! __isArray(argTypeSymbols)
   630 	    if (! __isArray(argTypeSymbols)
   589              || (__arraySize(argTypeSymbols) != __numArgs)) {
   631 	     || (__arraySize(argTypeSymbols) != __numArgs)) {
   590                 failureCode = @symbol(ArgumentCountMismatch);
   632 		failureCode = @symbol(ArgumentCountMismatch);
   591                 goto getOutOfHere;
   633 		goto getOutOfHere;
   592             }
   634 	    }
   593         }
   635 	}
   594     } else {
   636     } else {
   595         if (! __isArray(arguments)
   637 	if (! __isArray(arguments)
   596          || ! __isArray(argTypeSymbols)
   638 	 || ! __isArray(argTypeSymbols)
   597          || (__arraySize(argTypeSymbols) != (__numArgs = __arraySize(arguments)))) {
   639 	 || (__arraySize(argTypeSymbols) != (__numArgs = __arraySize(arguments)))) {
   598             failureCode = @symbol(ArgumentCountMismatch);
   640 	    failureCode = @symbol(ArgumentCountMismatch);
   599             goto getOutOfHere;
   641 	    goto getOutOfHere;
   600         }
   642 	}
   601     }
   643     }
   602     if (__numArgs > MAX_ARGS) {
   644     if (__numArgs > MAX_ARGS) {
   603         failureCode = @symbol(TooManyArguments);
   645 	failureCode = @symbol(TooManyArguments);
   604         goto getOutOfHere;
   646 	goto getOutOfHere;
   605     }
   647     }
   606 
   648 
   607     /*
   649     /*
   608      * validate the return type
   650      * validate the return type
   609      */
   651      */
   610     __returnValuePointer = &__returnValue;
   652     __returnValuePointer = &__returnValue;
   611 
   653 
   612     if (returnTypeSymbol == @symbol(voidPointer)) {
   654     if (returnTypeSymbol == @symbol(voidPointer)) {
   613         returnTypeSymbol = @symbol(handle);
   655 	returnTypeSymbol = @symbol(handle);
   614     }
   656     }
   615 
   657 
   616     if (returnTypeSymbol == @symbol(int)) {
   658     if (returnTypeSymbol == @symbol(int)) {
   617         __returnType = __get_ffi_type_sint();
   659 	__returnType = __get_ffi_type_sint();
   618     } else if (returnTypeSymbol == @symbol(uint)) {
   660     } else if (returnTypeSymbol == @symbol(uint)) {
   619         __returnType = __get_ffi_type_uint();
   661 	__returnType = __get_ffi_type_uint();
   620     } else if (returnTypeSymbol == @symbol(uint8)) {
   662     } else if (returnTypeSymbol == @symbol(uint8)) {
   621         __returnType = __get_ffi_type_uint8();
   663 	__returnType = __get_ffi_type_uint8();
   622     } else if (returnTypeSymbol == @symbol(uint16)) {
   664     } else if (returnTypeSymbol == @symbol(uint16)) {
   623         __returnType = __get_ffi_type_uint16();
   665 	__returnType = __get_ffi_type_uint16();
   624     } else if (returnTypeSymbol == @symbol(uint32)) {
   666     } else if (returnTypeSymbol == @symbol(uint32)) {
   625         __returnType = __get_ffi_type_uint32();
   667 	__returnType = __get_ffi_type_uint32();
   626     } else if (returnTypeSymbol == @symbol(uint64)) {
   668     } else if (returnTypeSymbol == @symbol(uint64)) {
   627         __returnType = __get_ffi_type_uint64();
   669 	__returnType = __get_ffi_type_uint64();
   628 
   670 
   629     } else if (returnTypeSymbol == @symbol(sint)) {
   671     } else if (returnTypeSymbol == @symbol(sint)) {
   630         __returnType = __get_ffi_type_sint();
   672 	__returnType = __get_ffi_type_sint();
   631     } else if (returnTypeSymbol == @symbol(sint8)) {
   673     } else if (returnTypeSymbol == @symbol(sint8)) {
   632         __returnType = __get_ffi_type_sint8();
   674 	__returnType = __get_ffi_type_sint8();
   633     } else if (returnTypeSymbol == @symbol(sint16)) {
   675     } else if (returnTypeSymbol == @symbol(sint16)) {
   634         __returnType = __get_ffi_type_sint16();
   676 	__returnType = __get_ffi_type_sint16();
   635     } else if (returnTypeSymbol == @symbol(sint32)) {
   677     } else if (returnTypeSymbol == @symbol(sint32)) {
   636         __returnType = __get_ffi_type_sint32();
   678 	__returnType = __get_ffi_type_sint32();
   637     } else if (returnTypeSymbol == @symbol(sint64)) {
   679     } else if (returnTypeSymbol == @symbol(sint64)) {
   638         __returnType = __get_ffi_type_sint64();
   680 	__returnType = __get_ffi_type_sint64();
   639 
   681 
   640     } else if (returnTypeSymbol == @symbol(long)) {
   682     } else if (returnTypeSymbol == @symbol(long)) {
   641         if (sizeof(long) == 4) {
   683 	if (sizeof(long) == 4) {
   642            returnTypeSymbol = @symbol(sint32);     
   684 	   returnTypeSymbol = @symbol(sint32);
   643            __returnType = __get_ffi_type_sint32();
   685 	   __returnType = __get_ffi_type_sint32();
   644         } else if (sizeof(long) == 8) {
   686 	} else if (sizeof(long) == 8) {
   645            returnTypeSymbol = @symbol(sint64);     
   687 	   returnTypeSymbol = @symbol(sint64);
   646            __returnType = __get_ffi_type_sint64();
   688 	   __returnType = __get_ffi_type_sint64();
   647         } else {
   689 	} else {
   648             failureCode = @symbol(UnknownReturnType);
   690 	    failureCode = @symbol(UnknownReturnType);
   649             goto getOutOfHere;
   691 	    goto getOutOfHere;
   650         }
   692 	}
   651 
   693 
   652     } else if (returnTypeSymbol == @symbol(ulong)) {
   694     } else if (returnTypeSymbol == @symbol(ulong)) {
   653         if (sizeof(long) == 4) {
   695 	if (sizeof(long) == 4) {
   654            returnTypeSymbol = @symbol(uint32);     
   696 	   returnTypeSymbol = @symbol(uint32);
   655            __returnType = __get_ffi_type_uint32();
   697 	   __returnType = __get_ffi_type_uint32();
   656         }else if (sizeof(long) == 8) {
   698 	}else if (sizeof(long) == 8) {
   657            returnTypeSymbol = @symbol(uint64);     
   699 	   returnTypeSymbol = @symbol(uint64);
   658            __returnType = __get_ffi_type_uint64();
   700 	   __returnType = __get_ffi_type_uint64();
   659         } else {
   701 	} else {
   660             failureCode = @symbol(UnknownReturnType);
   702 	    failureCode = @symbol(UnknownReturnType);
   661             goto getOutOfHere;
   703 	    goto getOutOfHere;
   662         }
   704 	}
   663 
   705 
   664     } else if (returnTypeSymbol == @symbol(boolean)) {
   706     } else if (returnTypeSymbol == @symbol(bool)) {
   665         __returnType = __get_ffi_type_uint();
   707 	__returnType = __get_ffi_type_uint();
   666 
   708 
   667     } else if (returnTypeSymbol == @symbol(float)) {
   709     } else if (returnTypeSymbol == @symbol(float)) {
   668         __returnType = __get_ffi_type_float();
   710 	__returnType = __get_ffi_type_float();
   669     } else if (returnTypeSymbol == @symbol(double)) {
   711     } else if (returnTypeSymbol == @symbol(double)) {
   670         __returnType = __get_ffi_type_double();
   712 	__returnType = __get_ffi_type_double();
   671 
   713 
   672     } else if (returnTypeSymbol == @symbol(void)) {
   714     } else if (returnTypeSymbol == @symbol(void)) {
   673         __returnType = __get_ffi_type_void();
   715 	__returnType = __get_ffi_type_void();
   674         __returnValuePointer = NULL;
   716 	__returnValuePointer = NULL;
   675     } else if ((returnTypeSymbol == @symbol(pointer)) || (returnTypeSymbol == @symbol(handle))) {
   717     } else if ((returnTypeSymbol == @symbol(pointer)) || (returnTypeSymbol == @symbol(handle))) {
   676         __returnType = __get_ffi_type_pointer();
   718 	__returnType = __get_ffi_type_pointer();
   677     } else if (returnTypeSymbol == @symbol(charPointer)) {
   719     } else if (returnTypeSymbol == @symbol(charPointer)) {
   678         __returnType = __get_ffi_type_pointer();
   720 	__returnType = __get_ffi_type_pointer();
   679     } else if (returnTypeSymbol == @symbol(wcharPointer)) {
   721     } else if (returnTypeSymbol == @symbol(wcharPointer)) {
   680         __returnType = __get_ffi_type_pointer();
   722 	__returnType = __get_ffi_type_pointer();
   681     } else {
   723     } else {
   682         if (__isSymbol(returnTypeSymbol)
   724 	if (__isSymbol(returnTypeSymbol)
   683          && ((returnValueClass = __GLOBAL_GET(returnTypeSymbol)) != nil)) {
   725 	 && ((returnValueClass = __GLOBAL_GET(returnTypeSymbol)) != nil)) {
   684             if (! __isBehaviorLike(returnValueClass)) {
   726 	    if (! __isBehaviorLike(returnValueClass)) {
   685                 failureCode = @symbol(NonBehaviorReturnType);
   727 		failureCode = @symbol(NonBehaviorReturnType);
   686                 goto getOutOfHere;
   728 		goto getOutOfHere;
   687             }
   729 	    }
   688             if (! __qIsSubclassOfExternalAddress(returnValueClass)) {
   730 	    if (! __qIsSubclassOfExternalAddress(returnValueClass)) {
   689                 failureCode = @symbol(NonExternalAddressReturnType);
   731 		failureCode = @symbol(NonExternalAddressReturnType);
   690                 goto getOutOfHere;
   732 		goto getOutOfHere;
   691             }
   733 	    }
   692             __returnType = __get_ffi_type_pointer();
   734 	    __returnType = __get_ffi_type_pointer();
   693             returnTypeSymbol = @symbol(pointer);
   735 	    returnTypeSymbol = @symbol(pointer);
   694         } else {
   736 	} else {
   695             failureCode = @symbol(UnknownReturnType);
   737 	    failureCode = @symbol(UnknownReturnType);
   696             goto getOutOfHere;
   738 	    goto getOutOfHere;
   697         }
   739 	}
   698     }
   740     }
   699 
   741 
   700     /*
   742     /*
   701      * validate the c++ object
   743      * validate the c++ object
   702      */
   744      */
   703     if (aCPlusPlusObjectOrNil != nil) {
   745     if (aCPlusPlusObjectOrNil != nil) {
   704         struct cPlusPlusInstance {
   746 	struct cPlusPlusInstance {
   705             void **vTable;
   747 	    void **vTable;
   706         };
   748 	};
   707         struct cPlusPlusInstance *inst;
   749 	struct cPlusPlusInstance *inst;
   708 
   750 
   709         if (__isExternalAddressLike(aCPlusPlusObjectOrNil)) {
   751 	if (__isExternalAddressLike(aCPlusPlusObjectOrNil)) {
   710             inst = (void *)(__externalAddressVal(aCPlusPlusObjectOrNil));
   752 	    inst = (void *)(__externalAddressVal(aCPlusPlusObjectOrNil));
   711         } else if (__isExternalBytesLike(aCPlusPlusObjectOrNil)) {
   753 	} else if (__isExternalBytesLike(aCPlusPlusObjectOrNil)) {
   712             inst = (void *)(__externalBytesVal(aCPlusPlusObjectOrNil));
   754 	    inst = (void *)(__externalBytesVal(aCPlusPlusObjectOrNil));
   713         } else {
   755 	} else {
   714             failureCode = @symbol(InvalidInstance);
   756 	    failureCode = @symbol(InvalidInstance);
   715             goto getOutOfHere;
   757 	    goto getOutOfHere;
   716         }
   758 	}
   717         __argValues[0].pointerVal = inst;
   759 	__argValues[0].pointerVal = inst;
   718         __argValuePointersIncludingThis[0] = &(__argValues[0]);
   760 	__argValuePointersIncludingThis[0] = &(__argValues[0]);
   719         __argTypes[0] = __get_ffi_type_pointer();
   761 	__argTypes[0] = __get_ffi_type_pointer();
   720 
   762 
   721         __argValuePointers = &__argValuePointersIncludingThis[1];
   763 	__argValuePointers = &__argValuePointersIncludingThis[1];
   722         __argTypes = &__argTypesIncludingThis[1];
   764 	__argTypes = &__argTypesIncludingThis[1];
   723         __argValues = &__argValuesIncludingThis[1];
   765 	__argValues = &__argValuesIncludingThis[1];
   724         __numArgsIncludingThis = __numArgs + 1;
   766 	__numArgsIncludingThis = __numArgs + 1;
   725 
   767 
   726         if (virtual == true) {
   768 	if (virtual == true) {
   727             if (! __isSmallInteger(vtOffset)) {
   769 	    if (! __isSmallInteger(vtOffset)) {
   728                 failureCode = @symbol(InvalidVTableIndex);
   770 		failureCode = @symbol(InvalidVTableIndex);
   729                 goto getOutOfHere;
   771 		goto getOutOfHere;
   730             }
   772 	    }
   731             codeAddress = inst->vTable[__intVal(vtOffset)];
   773 	    codeAddress = inst->vTable[__intVal(vtOffset)];
   732 #ifdef VERBOSE
   774 #ifdef VERBOSE
   733             printf("virtual codeAddress: %x\n", codeAddress);
   775 	    printf("virtual codeAddress: %x\n", codeAddress);
   734 #endif
   776 #endif
   735         }
   777 	}
   736     } else {
   778     } else {
   737         __numArgsIncludingThis = __numArgs;
   779 	__numArgsIncludingThis = __numArgs;
   738 #ifdef VERBOSE
   780 #ifdef VERBOSE
   739         printf("codeAddress: %x\n", codeAddress);
   781 	printf("codeAddress: %x\n", codeAddress);
   740 #endif
   782 #endif
   741     }
   783     }
   742 
   784 
   743     /*
   785     /*
   744      * validate all arg types and setup arg-buffers
   786      * validate all arg types and setup arg-buffers
   745      */
   787      */
   746     for (i=0; i<__numArgs; i++) {
   788     for (i=0; i<__numArgs; i++) {
   747         ffi_type *thisType;
   789 	ffi_type *thisType;
   748         void *argValuePtr;
   790 	void *argValuePtr;
   749         OBJ typeSymbol;
   791 	OBJ typeSymbol;
   750         OBJ arg;
   792 	OBJ arg;
   751 
   793 
   752         failureInfo = __mkSmallInteger(i+1);   /* in case there is one */
   794 	failureInfo = __mkSmallInteger(i+1);   /* in case there is one */
   753 
   795 
   754         typeSymbol = __ArrayInstPtr(argTypeSymbols)->a_element[i];
   796 	typeSymbol = __ArrayInstPtr(argTypeSymbols)->a_element[i];
   755         arg = __ArrayInstPtr(arguments)->a_element[i];
   797 	arg = __ArrayInstPtr(arguments)->a_element[i];
   756 
   798 
   757         if (typeSymbol == @symbol(handle)) {
   799 	if (typeSymbol == @symbol(handle)) {
   758             typeSymbol = @symbol(pointer);
   800 	    typeSymbol = @symbol(pointer);
   759         } else if (typeSymbol == @symbol(voidPointer)) {
   801 	} else if (typeSymbol == @symbol(voidPointer)) {
   760             typeSymbol = @symbol(pointer);
   802 	    typeSymbol = @symbol(pointer);
   761         }
   803 	}
   762 
   804 
   763         if (typeSymbol == @symbol(long)) {
   805 	if (typeSymbol == @symbol(long)) {
   764             if (sizeof(long) == sizeof(int)) {
   806 	    if (sizeof(long) == sizeof(int)) {
   765                 typeSymbol = @symbol(sint);
   807 		typeSymbol = @symbol(sint);
   766             } else {
   808 	    } else {
   767                 if (sizeof(long) == 4) {
   809 		if (sizeof(long) == 4) {
   768                     typeSymbol = @symbol(sint32);
   810 		    typeSymbol = @symbol(sint32);
   769                 } else if (sizeof(long) == 8) {
   811 		} else if (sizeof(long) == 8) {
   770                     typeSymbol = @symbol(sint64);
   812 		    typeSymbol = @symbol(sint64);
   771                 }
   813 		}
   772             }
   814 	    }
   773         }
   815 	}
   774         if (typeSymbol == @symbol(ulong)) {
   816 	if (typeSymbol == @symbol(ulong)) {
   775             if (sizeof(unsigned long) == sizeof(unsigned int)) {
   817 	    if (sizeof(unsigned long) == sizeof(unsigned int)) {
   776                 typeSymbol = @symbol(uint);
   818 		typeSymbol = @symbol(uint);
   777             } else {
   819 	    } else {
   778                 if (sizeof(long) == 4) {
   820 		if (sizeof(long) == 4) {
   779                     typeSymbol = @symbol(uint32);
   821 		    typeSymbol = @symbol(uint32);
   780                 } else if (sizeof(long) == 8) {
   822 		} else if (sizeof(long) == 8) {
   781                     typeSymbol = @symbol(uint64);
   823 		    typeSymbol = @symbol(uint64);
   782                 }
   824 		}
   783             }
   825 	    }
   784         }
   826 	}
   785 
   827 
   786         if (typeSymbol == @symbol(int)) {
   828 	if (typeSymbol == @symbol(int)) {
   787             thisType = __get_ffi_type_sint();
   829 	    thisType = __get_ffi_type_sint();
   788             if (__isSmallInteger(arg)) {
   830 	    if (__isSmallInteger(arg)) {
   789                 __argValues[i].iVal = __intVal(arg);
   831 		__argValues[i].iVal = __intVal(arg);
   790             } else {
   832 	    } else {
   791                 __argValues[i].iVal = __signedLongIntVal(arg);
   833 		__argValues[i].iVal = __signedLongIntVal(arg);
   792                 if (__argValues[i].iVal == 0) {
   834 		if (__argValues[i].iVal == 0) {
   793                     failureCode = @symbol(InvalidArgument);
   835 		    failureCode = @symbol(InvalidArgument);
   794                     goto getOutOfHere;
   836 		    goto getOutOfHere;
   795                 }
   837 		}
   796             }
   838 	    }
   797             argValuePtr = &(__argValues[i].iVal);
   839 	    argValuePtr = &(__argValues[i].iVal);
   798 
   840 
   799         } else if (typeSymbol == @symbol(uint)) {
   841 	} else if (typeSymbol == @symbol(uint)) {
   800             thisType = __get_ffi_type_uint();
   842 	    thisType = __get_ffi_type_uint();
   801 
   843 
   802             if (__isSmallInteger(arg)) {
   844 	    if (__isSmallInteger(arg)) {
   803                 __argValues[i].iVal = __intVal(arg);
   845 		__argValues[i].iVal = __intVal(arg);
   804             } else {
   846 	    } else {
   805                 __argValues[i].iVal = __unsignedLongIntVal(arg);
   847 		__argValues[i].iVal = __unsignedLongIntVal(arg);
   806                 if (__argValues[i].iVal == 0) {
   848 		if (__argValues[i].iVal == 0) {
   807                     failureCode = @symbol(InvalidArgument);
   849 		    failureCode = @symbol(InvalidArgument);
   808                     goto getOutOfHere;
   850 		    goto getOutOfHere;
   809                 }
   851 		}
   810             }
   852 	    }
   811             argValuePtr = &(__argValues[i].iVal);
   853 	    argValuePtr = &(__argValues[i].iVal);
   812 
   854 
   813         } else if (typeSymbol == @symbol(uint8)) {
   855 	} else if (typeSymbol == @symbol(uint8)) {
   814             thisType = __get_ffi_type_uint8();
   856 	    thisType = __get_ffi_type_uint8();
   815             if (! __isSmallInteger(arg)) {
   857 	    if (! __isSmallInteger(arg)) {
   816                 failureCode = @symbol(InvalidArgument);
   858 		failureCode = @symbol(InvalidArgument);
   817                 goto getOutOfHere;
   859 		goto getOutOfHere;
   818             }
   860 	    }
   819             __argValues[i].iVal = __intVal(arg);
   861 	    __argValues[i].iVal = __intVal(arg);
   820             if (((unsigned)(__argValues[i].iVal)) > 0xFF) {
   862 	    if (((unsigned)(__argValues[i].iVal)) > 0xFF) {
   821                 failureCode = @symbol(InvalidArgument);
   863 		failureCode = @symbol(InvalidArgument);
   822                 goto getOutOfHere;
   864 		goto getOutOfHere;
   823             }
   865 	    }
   824             argValuePtr = &(__argValues[i].iVal);
   866 	    argValuePtr = &(__argValues[i].iVal);
   825 
   867 
   826         } else if (typeSymbol == @symbol(sint8)) {
   868 	} else if (typeSymbol == @symbol(sint8)) {
   827             thisType = __get_ffi_type_sint8();
   869 	    thisType = __get_ffi_type_sint8();
   828             if (! __isSmallInteger(arg)) {
   870 	    if (! __isSmallInteger(arg)) {
   829                 failureCode = @symbol(InvalidArgument);
   871 		failureCode = @symbol(InvalidArgument);
   830                 goto getOutOfHere;
   872 		goto getOutOfHere;
   831             }
   873 	    }
   832             __argValues[i].iVal = __intVal(arg);
   874 	    __argValues[i].iVal = __intVal(arg);
   833             if (((__argValues[i].iVal) < -0x80) || ((__argValues[i].iVal) > 0x7F))  {
   875 	    if (((__argValues[i].iVal) < -0x80) || ((__argValues[i].iVal) > 0x7F))  {
   834                 failureCode = @symbol(InvalidArgument);
   876 		failureCode = @symbol(InvalidArgument);
   835                 goto getOutOfHere;
   877 		goto getOutOfHere;
   836             }
   878 	    }
   837             argValuePtr = &(__argValues[i].iVal);
   879 	    argValuePtr = &(__argValues[i].iVal);
   838 
   880 
   839         } else if (typeSymbol == @symbol(uint16)) {
   881 	} else if (typeSymbol == @symbol(uint16)) {
   840             thisType = __get_ffi_type_uint16();
   882 	    thisType = __get_ffi_type_uint16();
   841             if (! __isSmallInteger(arg)) {
   883 	    if (! __isSmallInteger(arg)) {
   842                 failureCode = @symbol(InvalidArgument);
   884 		failureCode = @symbol(InvalidArgument);
   843                 goto getOutOfHere;
   885 		goto getOutOfHere;
   844             }
   886 	    }
   845             __argValues[i].iVal = __intVal(arg);
   887 	    __argValues[i].iVal = __intVal(arg);
   846             if (((unsigned)(__argValues[i].iVal)) > 0xFFFF) {
   888 	    if (((unsigned)(__argValues[i].iVal)) > 0xFFFF) {
   847                 failureCode = @symbol(InvalidArgument);
   889 		failureCode = @symbol(InvalidArgument);
   848                 goto getOutOfHere;
   890 		goto getOutOfHere;
   849             }
   891 	    }
   850             argValuePtr = &(__argValues[i].iVal);
   892 	    argValuePtr = &(__argValues[i].iVal);
   851 
   893 
   852         } else if (typeSymbol == @symbol(sint16)) {
   894 	} else if (typeSymbol == @symbol(sint16)) {
   853             thisType = __get_ffi_type_sint16();
   895 	    thisType = __get_ffi_type_sint16();
   854             if (! __isSmallInteger(arg)) {
   896 	    if (! __isSmallInteger(arg)) {
   855                 failureCode = @symbol(InvalidArgument);
   897 		failureCode = @symbol(InvalidArgument);
   856                 goto getOutOfHere;
   898 		goto getOutOfHere;
   857             }
   899 	    }
   858             __argValues[i].iVal = __intVal(arg);
   900 	    __argValues[i].iVal = __intVal(arg);
   859             if (((__argValues[i].iVal) < -0x8000) || ((__argValues[i].iVal) > 0x7FFF))  {
   901 	    if (((__argValues[i].iVal) < -0x8000) || ((__argValues[i].iVal) > 0x7FFF))  {
   860                 failureCode = @symbol(InvalidArgument);
   902 		failureCode = @symbol(InvalidArgument);
   861                 goto getOutOfHere;
   903 		goto getOutOfHere;
   862             }
   904 	    }
   863             argValuePtr = &(__argValues[i].iVal);
   905 	    argValuePtr = &(__argValues[i].iVal);
   864 
   906 
   865         } else if ((typeSymbol == @symbol(uint32)) || (typeSymbol == @symbol(sint32))) {
   907 	} else if ((typeSymbol == @symbol(uint32)) || (typeSymbol == @symbol(sint32))) {
   866             thisType = __get_ffi_type_uint32();
   908 	    thisType = __get_ffi_type_uint32();
   867             if (__isSmallInteger(arg)) {
   909 	    if (__isSmallInteger(arg)) {
   868                 __argValues[i].iVal = __intVal(arg);
   910 		__argValues[i].iVal = __intVal(arg);
   869             } else {
   911 	    } else {
   870                 __argValues[i].iVal = __unsignedLongIntVal(arg);
   912 		__argValues[i].iVal = __unsignedLongIntVal(arg);
   871                 if (__argValues[i].iVal == 0) {
   913 		if (__argValues[i].iVal == 0) {
   872                     failureCode = @symbol(InvalidArgument);
   914 		    failureCode = @symbol(InvalidArgument);
   873                     goto getOutOfHere;
   915 		    goto getOutOfHere;
   874                 }
   916 		}
   875             }
   917 	    }
   876             argValuePtr = &(__argValues[i].iVal);
   918 	    argValuePtr = &(__argValues[i].iVal);
   877 
   919 
   878         } else if (typeSymbol == @symbol(float)) {
   920 	} else if (typeSymbol == @symbol(float)) {
   879             thisType = __get_ffi_type_float();
   921 	    thisType = __get_ffi_type_float();
   880             if (__isSmallInteger(arg)) {
   922 	    if (__isSmallInteger(arg)) {
   881                 __argValues[i].fVal = (float)(__intVal(arg));
   923 		__argValues[i].fVal = (float)(__intVal(arg));
   882             } else if (__isFloat(arg)) {
   924 	    } else if (__isFloat(arg)) {
   883                 __argValues[i].fVal = (float)(__floatVal(arg));
   925 		__argValues[i].fVal = (float)(__floatVal(arg));
   884             } else if (__isShortFloat(arg)) {
   926 	    } else if (__isShortFloat(arg)) {
   885                 __argValues[i].fVal = (float)(__shortFloatVal(arg));
   927 		__argValues[i].fVal = (float)(__shortFloatVal(arg));
   886             } else {
   928 	    } else {
   887                 failureCode = @symbol(InvalidArgument);
   929 		failureCode = @symbol(InvalidArgument);
   888                 goto getOutOfHere;
   930 		goto getOutOfHere;
   889             }
   931 	    }
   890             argValuePtr = &(__argValues[i].fVal);
   932 	    argValuePtr = &(__argValues[i].fVal);
   891 
   933 
   892         } else if (typeSymbol == @symbol(double)) {
   934 	} else if (typeSymbol == @symbol(double)) {
   893             thisType = __get_ffi_type_double();
   935 	    thisType = __get_ffi_type_double();
   894             if (__isSmallInteger(arg)) {
   936 	    if (__isSmallInteger(arg)) {
   895                 __argValues[i].dVal = (double)(__intVal(arg));
   937 		__argValues[i].dVal = (double)(__intVal(arg));
   896             } else if (__isFloat(arg)) {
   938 	    } else if (__isFloat(arg)) {
   897                 __argValues[i].dVal = (double)(__floatVal(arg));
   939 		__argValues[i].dVal = (double)(__floatVal(arg));
   898             } else if (__isShortFloat(arg)) {
   940 	    } else if (__isShortFloat(arg)) {
   899                 __argValues[i].dVal = (double)(__shortFloatVal(arg));
   941 		__argValues[i].dVal = (double)(__shortFloatVal(arg));
   900             } else {
   942 	    } else {
   901                 failureCode = @symbol(InvalidArgument);
   943 		failureCode = @symbol(InvalidArgument);
   902                 goto getOutOfHere;
   944 		goto getOutOfHere;
   903             }
   945 	    }
   904             argValuePtr = &(__argValues[i].dVal);
   946 	    argValuePtr = &(__argValues[i].dVal);
   905 
   947 
   906         } else if (typeSymbol == @symbol(void)) {
   948 	} else if (typeSymbol == @symbol(void)) {
   907             thisType = __get_ffi_type_void();
   949 	    thisType = __get_ffi_type_void();
   908             argValuePtr = &null;
   950 	    argValuePtr = &null;
   909 
   951 
   910         } else if (typeSymbol == @symbol(charPointer)) {
   952 	} else if (typeSymbol == @symbol(charPointer)) {
   911             thisType = __get_ffi_type_pointer();
   953 	    thisType = __get_ffi_type_pointer();
   912             if (__isString(arg) || __isSymbol(arg)) {
   954 	    if (__isString(arg) || __isSymbol(arg)) {
   913                 if (async == true) goto badArgForAsyncCall;
   955 		if (async == true) goto badArgForAsyncCall;
   914                 __argValues[i].pointerVal = (void *)(__stringVal(arg));
   956 		__argValues[i].pointerVal = (void *)(__stringVal(arg));
   915             } else {
   957 	    } else {
   916                 if (__isBytes(arg)) {
   958 		if (__isBytes(arg)) {
   917                     if (async == true) goto badArgForAsyncCall;
   959 		    if (async == true) goto badArgForAsyncCall;
   918                     __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
   960 		    __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
   919                 } else {
   961 		} else {
   920                     if (arg == nil) {
   962 		    if (arg == nil) {
   921                         __argValues[i].pointerVal = (void *)0;
   963 			__argValues[i].pointerVal = (void *)0;
   922                     } else {
   964 		    } else {
   923                         failureCode = @symbol(InvalidArgument);
   965 			failureCode = @symbol(InvalidArgument);
   924                         goto getOutOfHere;
   966 			goto getOutOfHere;
   925                     }
   967 		    }
   926                 }
   968 		}
   927             }
   969 	    }
   928             argValuePtr = &(__argValues[i].pointerVal);;
   970 	    argValuePtr = &(__argValues[i].pointerVal);;
   929 
   971 
   930         } else if (typeSymbol == @symbol(pointer)) {
   972 	} else if (typeSymbol == @symbol(pointer)) {
   931 commonPointerTypeArg: ;
   973 commonPointerTypeArg: ;
   932             thisType = __get_ffi_type_pointer();
   974 	    thisType = __get_ffi_type_pointer();
   933             if (arg == nil) {
   975 	    if (arg == nil) {
   934                 __argValues[i].pointerVal = NULL;
   976 		__argValues[i].pointerVal = NULL;
   935             } else if (__isExternalAddressLike(arg)) {
   977 	    } else if (__isExternalAddressLike(arg)) {
   936                 __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
   978 		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
   937             } else if (__isExternalBytesLike(arg)) {
   979 	    } else if (__isExternalBytesLike(arg)) {
   938                 __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
   980 		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
   939             } else if (__isByteArray(arg)) {
   981 	    } else if (__isByteArray(arg)) {
   940                 if (async == true) goto badArgForAsyncCall;
   982 		if (async == true) goto badArgForAsyncCall;
   941                 __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
   983 		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
   942             } else if (__isFloatArray(arg)) {
   984 	    } else if (__isFloatArray(arg)) {
   943                 if (async == true) goto badArgForAsyncCall;
   985 		if (async == true) goto badArgForAsyncCall;
   944                 __argValues[i].pointerVal = (void *)(__FloatArrayInstPtr(arg)->f_element);
   986 		__argValues[i].pointerVal = (void *)(__FloatArrayInstPtr(arg)->f_element);
   945             } else if (__isDoubleArray(arg)) {
   987 	    } else if (__isDoubleArray(arg)) {
   946                 if (async == true) goto badArgForAsyncCall;
   988 		if (async == true) goto badArgForAsyncCall;
   947                 __argValues[i].pointerVal = (void *)(__DoubleArrayInstPtr(arg)->d_element);
   989 		__argValues[i].pointerVal = (void *)(__DoubleArrayInstPtr(arg)->d_element);
   948             } else if (__isString(arg) || __isSymbol(arg)) {
   990 	    } else if (__isString(arg) || __isSymbol(arg)) {
   949                 if (async == true) {
   991 		if (async == true) {
   950 badArgForAsyncCall: ;
   992 badArgForAsyncCall: ;
   951                     failureCode = @symbol(BadArgForAsyncCall);
   993 		    failureCode = @symbol(BadArgForAsyncCall);
   952                     goto getOutOfHere;
   994 		    goto getOutOfHere;
   953                 }
   995 		}
   954                 __argValues[i].pointerVal = (void *)(__stringVal(arg));
   996 		__argValues[i].pointerVal = (void *)(__stringVal(arg));
   955             } else if (__isBytes(arg)) {
   997 	    } else if (__isBytes(arg)) {
   956                 char *p = (char *)(__byteArrayVal(arg));
   998 		char *p = (char *)(__byteArrayVal(arg));
   957                 int nInstBytes;
   999 		int nInstBytes;
   958                 OBJ cls;
  1000 		OBJ cls;
   959 
  1001 
   960                 cls = __qClass(arg);
  1002 		cls = __qClass(arg);
   961                 nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
  1003 		nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
   962                 __argValues[i].pointerVal = p + nInstBytes;
  1004 		__argValues[i].pointerVal = p + nInstBytes;
   963             } else {
  1005 	    } else {
   964                 failureCode = @symbol(InvalidArgument);
  1006 		failureCode = @symbol(InvalidArgument);
   965                 goto getOutOfHere;
  1007 		goto getOutOfHere;
   966             }
  1008 	    }
   967             argValuePtr = &(__argValues[i].pointerVal);;
  1009 	    argValuePtr = &(__argValues[i].pointerVal);;
   968 
  1010 
   969         } else if (typeSymbol == @symbol(boolean)) {
  1011 	} else if (typeSymbol == @symbol(bool)) {
   970             thisType = __get_ffi_type_uint();
  1012 	    thisType = __get_ffi_type_uint();
   971 
  1013 
   972             if (arg == true) {
  1014 	    if (arg == true) {
   973                 __argValues[i].iVal = 1;
  1015 		__argValues[i].iVal = 1;
   974             } else if (arg == false) {
  1016 	    } else if (arg == false) {
   975                 __argValues[i].iVal = 0;
  1017 		__argValues[i].iVal = 0;
   976             } else if (__isSmallInteger(arg)) {
  1018 	    } else if (__isSmallInteger(arg)) {
   977                 __argValues[i].iVal = __intVal(arg);
  1019 		__argValues[i].iVal = __intVal(arg);
   978             } else {
  1020 	    } else {
   979                 __argValues[i].iVal = __unsignedLongIntVal(arg);
  1021 		__argValues[i].iVal = __unsignedLongIntVal(arg);
   980                 if (__argValues[i].iVal == 0) {
  1022 		if (__argValues[i].iVal == 0) {
   981                     failureCode = @symbol(InvalidArgument);
  1023 		    failureCode = @symbol(InvalidArgument);
   982                     goto getOutOfHere;
  1024 		    goto getOutOfHere;
   983                 }
  1025 		}
   984             }
  1026 	    }
   985             argValuePtr = &(__argValues[i].iVal);
  1027 	    argValuePtr = &(__argValues[i].iVal);
   986         } else {
  1028 	} else {
   987             if (__isSymbol(typeSymbol)
  1029 	    if (__isSymbol(typeSymbol)
   988              && ((argValueClass = __GLOBAL_GET(typeSymbol)) != nil)) {
  1030 	     && ((argValueClass = __GLOBAL_GET(typeSymbol)) != nil)) {
   989                 if (! __isBehaviorLike(argValueClass)) {
  1031 		if (! __isBehaviorLike(argValueClass)) {
   990                     failureCode = @symbol(NonBehaviorArgumentType);
  1032 		    failureCode = @symbol(NonBehaviorArgumentType);
   991                     goto getOutOfHere;
  1033 		    goto getOutOfHere;
   992                 }
  1034 		}
   993                 if (! __qIsSubclassOfExternalAddress(argValueClass)) {
  1035 		if (! __qIsSubclassOfExternalAddress(argValueClass)) {
   994                     failureCode = @symbol(NonExternalAddressArgumentType);
  1036 		    failureCode = @symbol(NonExternalAddressArgumentType);
   995                     goto getOutOfHere;
  1037 		    goto getOutOfHere;
   996                 }
  1038 		}
   997                 goto commonPointerTypeArg; /* sorry */
  1039 		goto commonPointerTypeArg; /* sorry */
   998             } else {
  1040 	    } else {
   999                 failureCode = @symbol(UnknownArgumentType);
  1041 		failureCode = @symbol(UnknownArgumentType);
  1000                 goto getOutOfHere;
  1042 		goto getOutOfHere;
  1001             }
  1043 	    }
  1002         }
  1044 	}
  1003 
  1045 
  1004         __argTypes[i] = thisType;
  1046 	__argTypes[i] = thisType;
  1005         __argValuePointers[i] = argValuePtr;
  1047 	__argValuePointers[i] = argValuePtr;
  1006 
  1048 
  1007 #ifdef VERBOSE
  1049 #ifdef VERBOSE
  1008         printf("arg%d: %x\n", i, __argValues[i].iVal);
  1050 	printf("arg%d: %x\n", i, __argValues[i].iVal);
  1009 #endif
  1051 #endif
  1010     }
  1052     }
  1011     failureInfo = nil;
  1053     failureInfo = nil;
  1012 
  1054 
  1013     __callType = FFI_DEFAULT_ABI;
  1055     __callType = FFI_DEFAULT_ABI;
  1014 
  1056 
  1015 #ifdef CALLTYPE_FFI_STDCALL
  1057 #ifdef CALLTYPE_FFI_STDCALL
  1016     if (callTypeNumber == @global(CALLTYPE_API)) {
  1058     if (callTypeNumber == @global(CALLTYPE_API)) {
  1017         __callType = CALLTYPE_FFI_STDCALL;
  1059 	__callType = CALLTYPE_FFI_STDCALL;
  1018     }
  1060     }
  1019 #endif
  1061 #endif
  1020 #ifdef CALLTYPE_FFI_V8
  1062 #ifdef CALLTYPE_FFI_V8
  1021     if (callTypeNumber == @global(CALLTYPE_V8)) {
  1063     if (callTypeNumber == @global(CALLTYPE_V8)) {
  1022         __callType = CALLTYPE_FFI_V8;
  1064 	__callType = CALLTYPE_FFI_V8;
  1023     }
  1065     }
  1024 #endif
  1066 #endif
  1025 #ifdef CALLTYPE_FFI_V9
  1067 #ifdef CALLTYPE_FFI_V9
  1026     if (callTypeNumber == @global(CALLTYPE_V9)) {
  1068     if (callTypeNumber == @global(CALLTYPE_V9)) {
  1027         __callType = CALLTYPE_FFI_V9;
  1069 	__callType = CALLTYPE_FFI_V9;
  1028     }
  1070     }
  1029 #endif
  1071 #endif
  1030 #ifdef CALLTYPE_FFI_UNIX64
  1072 #ifdef CALLTYPE_FFI_UNIX64
  1031     if (callTypeNumber == @global(CALLTYPE_UNIX64)) {
  1073     if (callTypeNumber == @global(CALLTYPE_UNIX64)) {
  1032         __callType = CALLTYPE_FFI_UNIX64;
  1074 	__callType = CALLTYPE_FFI_UNIX64;
  1033     }
  1075     }
  1034 #endif
  1076 #endif
  1035 
  1077 
  1036     if (ffi_prep_cif(&__cif, __callType, __numArgsIncludingThis, __returnType, __argTypesIncludingThis) != FFI_OK) {
  1078     if (ffi_prep_cif(&__cif, __callType, __numArgsIncludingThis, __returnType, __argTypesIncludingThis) != FFI_OK) {
  1037         failureCode = @symbol(FFIPrepareFailed);
  1079 	failureCode = @symbol(FFIPrepareFailed);
  1038         goto getOutOfHere;
  1080 	goto getOutOfHere;
  1039     }
  1081     }
  1040     if (async == true) {
  1082     if (async == true) {
  1041 #ifdef VERBOSE
  1083 #ifdef VERBOSE
  1042         printf("async call 0x%x\n", codeAddress);
  1084 	printf("async call 0x%x\n", codeAddress);
  1043 #endif
  1085 #endif
  1044 #ifdef WIN32
  1086 #ifdef WIN32
  1045         __STX_C_CALL4( "ffi_call", ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1087 	__STX_C_CALL4( "ffi_call", ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1046 #else
  1088 #else
  1047         __BEGIN_INTERRUPTABLE__
  1089 	__BEGIN_INTERRUPTABLE__
  1048         ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1090 	ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1049         __END_INTERRUPTABLE__
  1091 	__END_INTERRUPTABLE__
  1050 #endif
  1092 #endif
  1051     } else {
  1093     } else {
  1052         if (unlimitedStack == true) {
  1094 	if (unlimitedStack == true) {
  1053 #ifdef VERBOSE
  1095 #ifdef VERBOSE
  1054             printf("UNLIMITEDSTACKCALL call 0x%x\n", codeAddress);
  1096 	    printf("UNLIMITEDSTACKCALL call 0x%x\n", codeAddress);
  1055 #endif
  1097 #endif
  1056 #if 0
  1098 #if 0
  1057             __UNLIMITEDSTACKCALL__(ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1099 	    __UNLIMITEDSTACKCALL__(ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1058 #endif
  1100 #endif
  1059         } else {
  1101 	} else {
  1060 #ifdef VERBOSE
  1102 #ifdef VERBOSE
  1061             printf("call 0x%x\n", codeAddress);
  1103 	    printf("call 0x%x\n", codeAddress);
  1062 #endif
  1104 #endif
  1063             ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1105 	    ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1064         }
  1106 	}
  1065     }
  1107     }
  1066 #ifdef VERBOSE
  1108 #ifdef VERBOSE
  1067     printf("retval is %d (0x%x)\n", __returnValue.iVal, __returnValue.iVal);
  1109     printf("retval is %d (0x%x)\n", __returnValue.iVal, __returnValue.iVal);
  1068 #endif
  1110 #endif
  1069     if ((returnTypeSymbol == @symbol(sint))
  1111     if ((returnTypeSymbol == @symbol(sint))
  1070      || (returnTypeSymbol == @symbol(sint8))
  1112      || (returnTypeSymbol == @symbol(sint8))
  1071      || (returnTypeSymbol == @symbol(sint16))
  1113      || (returnTypeSymbol == @symbol(sint16))
  1072      || (returnTypeSymbol == @symbol(sint32))) {
  1114      || (returnTypeSymbol == @symbol(sint32))) {
  1073         RETURN ( __MKINT(__returnValue.iVal) );
  1115 	RETURN ( __MKINT(__returnValue.iVal) );
  1074     }
  1116     }
  1075     if ((returnTypeSymbol == @symbol(uint))
  1117     if ((returnTypeSymbol == @symbol(uint))
  1076      || (returnTypeSymbol == @symbol(uint8))
  1118      || (returnTypeSymbol == @symbol(uint8))
  1077      || (returnTypeSymbol == @symbol(uint16))
  1119      || (returnTypeSymbol == @symbol(uint16))
  1078      || (returnTypeSymbol == @symbol(uint32))) {
  1120      || (returnTypeSymbol == @symbol(uint32))) {
  1079         RETURN ( __MKUINT(__returnValue.iVal) );
  1121 	RETURN ( __MKUINT(__returnValue.iVal) );
  1080     }
  1122     }
  1081     if (returnTypeSymbol == @symbol(boolean)) {
  1123     if (returnTypeSymbol == @symbol(bool)) {
  1082         RETURN ( __returnValue.iVal ? true : false );
  1124 	RETURN ( __returnValue.iVal ? true : false );
  1083     }
  1125     }
  1084     if (returnTypeSymbol == @symbol(float)) {
  1126     if (returnTypeSymbol == @symbol(float)) {
  1085         RETURN ( __MKFLOAT(__returnValue.fVal ));
  1127 	RETURN ( __MKFLOAT(__returnValue.fVal ));
  1086     }
  1128     }
  1087     if (returnTypeSymbol == @symbol(double)) {
  1129     if (returnTypeSymbol == @symbol(double)) {
  1088         RETURN ( __MKFLOAT(__returnValue.dVal ));
  1130 	RETURN ( __MKFLOAT(__returnValue.dVal ));
  1089     }
  1131     }
  1090     if (returnTypeSymbol == @symbol(void)) {
  1132     if (returnTypeSymbol == @symbol(void)) {
  1091         RETURN ( nil );
  1133 	RETURN ( nil );
  1092     }
  1134     }
  1093     if (returnTypeSymbol == @symbol(char)) {
  1135     if (returnTypeSymbol == @symbol(char)) {
  1094         RETURN ( __MKCHARACTER(__returnValue.iVal & 0xFF) );
  1136 	RETURN ( __MKCHARACTER(__returnValue.iVal & 0xFF) );
  1095     }
  1137     }
  1096     if (returnTypeSymbol == @symbol(wchar)) {
  1138     if (returnTypeSymbol == @symbol(wchar)) {
  1097         RETURN ( __MKUCHARACTER(__returnValue.iVal & 0xFFFF) );
  1139 	RETURN ( __MKUCHARACTER(__returnValue.iVal & 0xFFFF) );
  1098     }
  1140     }
  1099     if (returnTypeSymbol == @symbol(handle)) {
  1141     if (returnTypeSymbol == @symbol(handle)) {
  1100         returnValue = __MKEXTERNALADDRESS(__returnValue.pointerVal);
  1142 	returnValue = __MKEXTERNALADDRESS(__returnValue.pointerVal);
  1101     } else if (returnTypeSymbol == @symbol(pointer)) {
  1143     } else if (returnTypeSymbol == @symbol(pointer)) {
  1102         returnValue = __MKEXTERNALBYTES(__returnValue.pointerVal);
  1144 	returnValue = __MKEXTERNALBYTES(__returnValue.pointerVal);
  1103     } else if (returnTypeSymbol == @symbol(charPointer)) {
  1145     } else if (returnTypeSymbol == @symbol(charPointer)) {
  1104         returnValue = __MKSTRING(__returnValue.pointerVal);
  1146 	returnValue = __MKSTRING(__returnValue.pointerVal);
  1105     } else if (returnTypeSymbol == @symbol(wcharPointer)) {
  1147     } else if (returnTypeSymbol == @symbol(wcharPointer)) {
  1106         returnValue = __MKU16STRING(__returnValue.pointerVal);
  1148 	returnValue = __MKU16STRING(__returnValue.pointerVal);
  1107     } else {
  1149     } else {
  1108         failureCode = @symbol(UnknownReturnType2);
  1150 	failureCode = @symbol(UnknownReturnType2);
  1109     }
  1151     }
  1110 getOutOfHere: ;
  1152 getOutOfHere: ;
  1111 
  1153 
  1112 #else /* no FFI support */
  1154 #else /* no FFI support */
  1113     failureCode = @symbol(FFINotSupported);
  1155     failureCode = @symbol(FFINotSupported);
  1114 #endif /* HAVE_FFI */
  1156 #endif /* HAVE_FFI */
  1115 %}.
  1157 %}.
  1116     failureCode notNil ifTrue:[
  1158     failureCode notNil ifTrue:[
  1117         self primitiveFailed.
  1159 	self primitiveFailed.
  1118         ^ nil
  1160 	^ nil
  1119     ].
  1161     ].
  1120 
  1162 
  1121     returnType isSymbol ifTrue:[
  1163     returnType isSymbol ifTrue:[
  1122         returnValueClass notNil ifTrue:[
  1164 	returnValueClass notNil ifTrue:[
  1123             self isConstReturnValue ifTrue:[
  1165 	    self isConstReturnValue ifTrue:[
  1124                 returnValue changeClassTo:returnValueClass.
  1166 		returnValue changeClassTo:returnValueClass.
  1125                 ^ returnValue
  1167 		^ returnValue
  1126             ].
  1168 	    ].
  1127             ^ returnValueClass fromExternalAddress:returnValue.
  1169 	    ^ returnValueClass fromExternalAddress:returnValue.
  1128         ].
  1170 	].
  1129     ] ifFalse:[
  1171     ] ifFalse:[
  1130         returnType isCPointer ifTrue:[
  1172 	returnType isCPointer ifTrue:[
  1131             returnType baseType isCStruct ifTrue:[
  1173 	    returnType baseType isCStruct ifTrue:[
  1132                 stClass := Smalltalk classNamed:returnType baseType name.
  1174 		stClass := Smalltalk classNamed:returnType baseType name.
  1133                 stClass notNil ifTrue:[
  1175 		stClass notNil ifTrue:[
  1134                     self isConstReturnValue ifTrue:[
  1176 		    self isConstReturnValue ifTrue:[
  1135                         returnValue changeClassTo:returnValueClass.
  1177 			returnValue changeClassTo:returnValueClass.
  1136                         ^ returnValue
  1178 			^ returnValue
  1137                     ].
  1179 		    ].
  1138                     ^ stClass fromExternalAddress:returnValue.
  1180 		    ^ stClass fromExternalAddress:returnValue.
  1139                 ].
  1181 		].
  1140             ].
  1182 	    ].
  1141             returnType baseType isCChar ifTrue:[
  1183 	    returnType baseType isCChar ifTrue:[
  1142                 ^ returnValue stringAt:1
  1184 		^ returnValue stringAt:1
  1143             ].
  1185 	    ].
  1144         ].
  1186 	].
  1145     ].
  1187     ].
  1146 
  1188 
  1147     ^ returnValue
  1189     ^ returnValue
  1148 
  1190 
  1149     "Created: / 01-08-2006 / 13:56:23 / cg"
  1191     "Created: / 01-08-2006 / 13:56:23 / cg"
  1151 ! !
  1193 ! !
  1152 
  1194 
  1153 !ExternalLibraryFunction class methodsFor:'documentation'!
  1195 !ExternalLibraryFunction class methodsFor:'documentation'!
  1154 
  1196 
  1155 version
  1197 version
  1156     ^ '$Header: /cvs/stx/stx/libbasic/ExternalLibraryFunction.st,v 1.44 2006-09-20 10:10:43 stefan Exp $'
  1198     ^ '$Header: /cvs/stx/stx/libbasic/ExternalLibraryFunction.st,v 1.45 2006-10-04 09:10:37 cg Exp $'
  1157 ! !
  1199 ! !
  1158 
  1200 
  1159 ExternalLibraryFunction initialize!
  1201 ExternalLibraryFunction initialize!