ExternalLibraryFunction.st
changeset 14625 290463096ff5
parent 14516 359e4d2234af
child 14632 6fe0dc1d5377
equal deleted inserted replaced
14624:58ad30334e84 14625:290463096ff5
    42 extern ffi_type *__get_ffi_type_double();
    42 extern ffi_type *__get_ffi_type_double();
    43 extern ffi_type *__get_ffi_type_void();
    43 extern ffi_type *__get_ffi_type_void();
    44 extern ffi_type *__get_ffi_type_pointer();
    44 extern ffi_type *__get_ffi_type_pointer();
    45 
    45 
    46 #else
    46 #else
    47 #error "HAVE_FFI not defined!"
    47 # error "HAVE_FFI not defined!"
    48 #endif
    48 #endif
    49 
    49 
    50 %}
    50 %}
    51 ! !
    51 ! !
    52 
    52 
    69 documentation
    69 documentation
    70 "
    70 "
    71     instances of me are used to interface to external library functions (as found in a dll/shared object).
    71     instances of me are used to interface to external library functions (as found in a dll/shared object).
    72 
    72 
    73     Inside a method, when a special external-call pragma such as:
    73     Inside a method, when a special external-call pragma such as:
    74         <api: bool MessageBeep(uint)>
    74 	<api: bool MessageBeep(uint)>
    75 
    75 
    76     is encountered by the parser, the compiler generates a call via
    76     is encountered by the parser, the compiler generates a call via
    77         <correspondingExternalLibraryFunctionObject> invokeWithArguments: argumentArray.
    77 	<correspondingExternalLibraryFunctionObject> invokeWithArguments: argumentArray.
    78 
    78 
    79     In the invoke method, the library is checked to be loaded (and loaded if not already),
    79     In the invoke method, the library is checked to be loaded (and loaded if not already),
    80     the arguments are converted to C and pushed onto the C-stack, the function is called,
    80     the arguments are converted to C and pushed onto the C-stack, the function is called,
    81     and finally, the return value is converted back from C to a smalltalk object.
    81     and finally, the return value is converted back from C to a smalltalk object.
    82 
    82 
    83     The parser supports the call-syntax of various other smalltalk dialects:
    83     The parser supports the call-syntax of various other smalltalk dialects:
    84         Squeak / ST-X:
    84 	Squeak / ST-X:
    85             <cdecl:   [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName > 
    85 	    <cdecl:   [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >
    86             <apicall: [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >
    86 	    <apicall: [async] [virtual|nonVirtual][const] returnType functionNameStringOrIndex ( argType1..argTypeN ) module: moduleName >
    87 
    87 
    88         Dolphin:
    88 	Dolphin:
    89             <stdcall: [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>
    89 	    <stdcall: [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>
    90             <cdecl:   [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN> 
    90 	    <cdecl:   [virtual|nonVirtual][const] returnType functionNameStringOrIndex argType1..argTypeN>
    91 
    91 
    92         ST/V:
    92 	ST/V:
    93             <api: functionName argType1 .. argTypeN returnType> 
    93 	    <api: functionName argType1 .. argTypeN returnType>
    94             <ccall: functionName argType1 .. argTypeN returnType> 
    94 	    <ccall: functionName argType1 .. argTypeN returnType>
    95             <ole: vFunctionIndex argType1 .. argTypeN returnType>
    95 	    <ole: vFunctionIndex argType1 .. argTypeN returnType>
    96 
    96 
    97         VisualWorks:
    97 	VisualWorks:
    98             <c: ...>
    98 	    <c: ...>
    99             <c: #define NAME value>
    99 	    <c: #define NAME value>
   100 "
   100 "
   101 !
   101 !
   102 
   102 
   103 example
   103 example
   104 "
   104 "
   105                                                                 [exBegin]
   105 								[exBegin]
   106         |f|
   106 	|f|
   107 
   107 
   108         f := ExternalLibraryFunction new.
   108 	f := ExternalLibraryFunction new.
   109         f beCallTypeWINAPI.
   109 	f beCallTypeWINAPI.
   110 
   110 
   111         f name:'MessageBeep'
   111 	f name:'MessageBeep'
   112           module:'user32.dll'
   112 	  module:'user32.dll'
   113           returnType:#boolean
   113 	  returnType:#boolean
   114           argumentTypes:#(uint).
   114 	  argumentTypes:#(uint).
   115 
   115 
   116         f invokeWith:1.
   116 	f invokeWith:1.
   117                                                                 [exEnd]
   117 								[exEnd]
   118 
   118 
   119   Synchronous vs. Asynchronous calls:
   119   Synchronous vs. Asynchronous calls:
   120 
   120 
   121     by default, foreign function calls are synchronous, effectively blocking the whole ST/X system
   121     by default, foreign function calls are synchronous, effectively blocking the whole ST/X system
   122     (that is by purpose,ībecause most C-code is not prepared for being interrupted, and also, normal
   122     (that is by purpose,ībecause most C-code is not prepared for being interrupted, and also, normal
   123      code is not prepared for a garbage collector to move objects around, while another C thread might
   123      code is not prepared for a garbage collector to move objects around, while another C thread might
   124      access the data...).
   124      access the data...).
   125     Therefore, the following will block all ST/X activity for 10 seconds 
   125     Therefore, the following will block all ST/X activity for 10 seconds
   126     (try interacting with the launcher while the Sleep is performing):
   126     (try interacting with the launcher while the Sleep is performing):
   127 
   127 
   128                                                                 [exBegin]
   128 								[exBegin]
   129         |f|
   129 	|f|
   130 
   130 
   131         f := ExternalLibraryFunction new.
   131 	f := ExternalLibraryFunction new.
   132         f beCallTypeWINAPI.
   132 	f beCallTypeWINAPI.
   133 
   133 
   134         f name:'Sleep'
   134 	f name:'Sleep'
   135           module:'kernel32.dll'
   135 	  module:'kernel32.dll'
   136           returnType:#void
   136 	  returnType:#void
   137           argumentTypes:#(uint).
   137 	  argumentTypes:#(uint).
   138 
   138 
   139         f invokeWith:10000.
   139 	f invokeWith:10000.
   140                                                                 [exEnd]
   140 								[exEnd]
   141 
   141 
   142     if you know what you do and you do not pass any possibly moving objects (such as strings) as argument,
   142     if you know what you do and you do not pass any possibly moving objects (such as strings) as argument,
   143     the call can be made asynchronous. In that case, ONLY the calling thread will be blocked; all other smalltalk
   143     the call can be made asynchronous. In that case, ONLY the calling thread will be blocked; all other smalltalk
   144     threads wil continue to execute.
   144     threads wil continue to execute.
   145     (try interacting now with the launcher while the Sleep is performing):
   145     (try interacting now with the launcher while the Sleep is performing):
   146                                                                 [exBegin]
   146 								[exBegin]
   147         |f|
   147 	|f|
   148 
   148 
   149         f := ExternalLibraryFunction new.
   149 	f := ExternalLibraryFunction new.
   150         f beCallTypeWINAPI.
   150 	f beCallTypeWINAPI.
   151         f beAsync.
   151 	f beAsync.
   152 
   152 
   153         f name:'Sleep'
   153 	f name:'Sleep'
   154           module:'kernel32.dll'
   154 	  module:'kernel32.dll'
   155           returnType:#void
   155 	  returnType:#void
   156           argumentTypes:#(uint).
   156 	  argumentTypes:#(uint).
   157 
   157 
   158         f invokeWith:10000.
   158 	f invokeWith:10000.
   159                                                                 [exEnd]
   159 								[exEnd]
   160 
   160 
   161 "
   161 "
   162 ! !
   162 ! !
   163 
   163 
   164 !ExternalLibraryFunction class methodsFor:'instance creation'!
   164 !ExternalLibraryFunction class methodsFor:'instance creation'!
   185 !
   185 !
   186 
   186 
   187 dllMapping
   187 dllMapping
   188     "allows for dll's to be replaced,
   188     "allows for dll's to be replaced,
   189      for example, if you want to use the mozilla sqlite dll
   189      for example, if you want to use the mozilla sqlite dll
   190         C:\Program Files\Mozilla Firefox\mozsqlite3.dll
   190 	C:\Program Files\Mozilla Firefox\mozsqlite3.dll
   191      for the sqlite3, execute:
   191      for the sqlite3, execute:
   192         ExternalLibraryFunction 
   192 	ExternalLibraryFunction
   193             dllMapping at:'sqlite3'
   193 	    dllMapping at:'sqlite3'
   194             put: 'C:\Program Files\Mozilla Firefox\mozsqlite3.dll'
   194 	    put: 'C:\Program Files\Mozilla Firefox\mozsqlite3.dll'
   195     "
   195     "
   196 
   196 
   197     DllMapping isNil ifTrue:[
   197     DllMapping isNil ifTrue:[
   198         DllMapping := Dictionary new.
   198 	DllMapping := Dictionary new.
   199     ].
   199     ].
   200     ^ DllMapping
   200     ^ DllMapping
   201 
   201 
   202     "Created: / 10-04-2012 / 12:21:45 / cg"
   202     "Created: / 10-04-2012 / 12:21:45 / cg"
   203 !
   203 !
   212 
   212 
   213 initialize
   213 initialize
   214     "using inline access to corresponding c--defines to avoid duplicate places of knowledge"
   214     "using inline access to corresponding c--defines to avoid duplicate places of knowledge"
   215 
   215 
   216     DLLPATH isNil ifTrue:[
   216     DLLPATH isNil ifTrue:[
   217         DLLPATH := #('.').
   217 	DLLPATH := #('.').
   218         FLAG_VIRTUAL := %{ __MKSMALLINT(__EXTL_FLAG_VIRTUAL) %}.                "/ a virtual c++ call
   218 	FLAG_VIRTUAL := %{ __MKSMALLINT(__EXTL_FLAG_VIRTUAL) %}.                "/ a virtual c++ call
   219         FLAG_NONVIRTUAL := %{ __MKSMALLINT(__EXTL_FLAG_NONVIRTUAL) %}.          "/ a non-virtual c++ call
   219 	FLAG_NONVIRTUAL := %{ __MKSMALLINT(__EXTL_FLAG_NONVIRTUAL) %}.          "/ a non-virtual c++ call
   220         FLAG_UNLIMITEDSTACK := %{ __MKSMALLINT(__EXTL_FLAG_UNLIMITEDSTACK) %}.  "/ unlimitedstack under unix
   220 	FLAG_UNLIMITEDSTACK := %{ __MKSMALLINT(__EXTL_FLAG_UNLIMITEDSTACK) %}.  "/ unlimitedstack under unix
   221         FLAG_ASYNC := %{ __MKSMALLINT(__EXTL_FLAG_ASYNC) %}.                    "/ async under win32
   221 	FLAG_ASYNC := %{ __MKSMALLINT(__EXTL_FLAG_ASYNC) %}.                    "/ async under win32
   222         FLAG_RETVAL_IS_CONST := %{ __MKSMALLINT(__EXTL_FLAG_RETVAL_IS_CONST) %}."/ return value is not to be registered for finalization
   222 	FLAG_RETVAL_IS_CONST := %{ __MKSMALLINT(__EXTL_FLAG_RETVAL_IS_CONST) %}."/ return value is not to be registered for finalization
   223 
   223 
   224         CALLTYPE_API := %{ __MKSMALLINT(__EXTL_CALLTYPE_API) %}.                "/ WINAPI-call (win32 only)
   224 	CALLTYPE_API := %{ __MKSMALLINT(__EXTL_CALLTYPE_API) %}.                "/ WINAPI-call (win32 only)
   225         CALLTYPE_C := %{ __MKSMALLINT(__EXTL_CALLTYPE_C) %}.                    "/ regular C-call (the default)
   225 	CALLTYPE_C := %{ __MKSMALLINT(__EXTL_CALLTYPE_C) %}.                    "/ regular C-call (the default)
   226         CALLTYPE_V8 := %{ __MKSMALLINT(__EXTL_CALLTYPE_V8) %}.                  "/ v8 call (sparc only)
   226 	CALLTYPE_V8 := %{ __MKSMALLINT(__EXTL_CALLTYPE_V8) %}.                  "/ v8 call (sparc only)
   227         CALLTYPE_V9 := %{ __MKSMALLINT(__EXTL_CALLTYPE_V9) %}.                  "/ v9 call (sparc only)
   227 	CALLTYPE_V9 := %{ __MKSMALLINT(__EXTL_CALLTYPE_V9) %}.                  "/ v9 call (sparc only)
   228         CALLTYPE_UNIX64 := %{ __MKSMALLINT(__EXTL_CALLTYPE_UNIX64) %}.          "/ unix64 call (alpha only)
   228 	CALLTYPE_UNIX64 := %{ __MKSMALLINT(__EXTL_CALLTYPE_UNIX64) %}.          "/ unix64 call (alpha only)
   229 
   229 
   230         CALLTYPE_MASK := %{ __MKSMALLINT(__EXTL_CALLTYPE_MASK) %}.
   230 	CALLTYPE_MASK := %{ __MKSMALLINT(__EXTL_CALLTYPE_MASK) %}.
   231     ].
   231     ].
   232 
   232 
   233     "
   233     "
   234      self initialize
   234      self initialize
   235     "
   235     "
   568 !ExternalLibraryFunction methodsFor:'printing'!
   568 !ExternalLibraryFunction methodsFor:'printing'!
   569 
   569 
   570 printOn:aStream
   570 printOn:aStream
   571     aStream nextPutAll:'<'.
   571     aStream nextPutAll:'<'.
   572     self isCallTypeAPI ifTrue:[
   572     self isCallTypeAPI ifTrue:[
   573         'API:' printOn:aStream.
   573 	'API:' printOn:aStream.
   574     ] ifFalse:[
   574     ] ifFalse:[
   575         self isCallTypeOLE ifTrue:[
   575 	self isCallTypeOLE ifTrue:[
   576             'OLE:' printOn:aStream.
   576 	    'OLE:' printOn:aStream.
   577         ] ifFalse:[
   577 	] ifFalse:[
   578             self isCallTypeC ifTrue:[
   578 	    self isCallTypeC ifTrue:[
   579                 'C:' printOn:aStream.
   579 		'C:' printOn:aStream.
   580             ] ifFalse:[
   580 	    ] ifFalse:[
   581                 self error.
   581 		self error.
   582             ].
   582 	    ].
   583         ].
   583 	].
   584     ].
   584     ].
   585     aStream nextPutAll:' '.
   585     aStream nextPutAll:' '.
   586     name printOn:aStream.
   586     name printOn:aStream.
   587     moduleName notNil ifTrue:[
   587     moduleName notNil ifTrue:[
   588         aStream nextPutAll:' module:'.
   588 	aStream nextPutAll:' module:'.
   589         moduleName printOn:aStream.
   589 	moduleName printOn:aStream.
   590     ].
   590     ].
   591     aStream nextPutAll:'>'.
   591     aStream nextPutAll:'>'.
   592 
   592 
   593     "Modified: / 25-09-2012 / 12:06:14 / cg"
   593     "Modified: / 25-09-2012 / 12:06:14 / cg"
   594 ! !
   594 ! !
   607      I.e. retrieve the module handle and the code pointer."
   607      I.e. retrieve the module handle and the code pointer."
   608 
   608 
   609     |handle moduleNameUsed functionName|
   609     |handle moduleNameUsed functionName|
   610 
   610 
   611     name isNumber ifTrue:[
   611     name isNumber ifTrue:[
   612         self isCPPFunction ifTrue:[
   612 	self isCPPFunction ifTrue:[
   613             "/ no need to load a dll.
   613 	    "/ no need to load a dll.
   614             ^ self
   614 	    ^ self
   615         ]
   615 	]
   616     ].
   616     ].
   617 
   617 
   618     "/ in some other smalltalks, there is no moduleName in the ffi-spec;
   618     "/ in some other smalltalks, there is no moduleName in the ffi-spec;
   619     "/ instead, the class provides the libraryName...
   619     "/ instead, the class provides the libraryName...
   620     (moduleNameUsed := moduleName) isNil ifTrue:[
   620     (moduleNameUsed := moduleName) isNil ifTrue:[
   621         owningClass isNil ifTrue:[
   621 	owningClass isNil ifTrue:[
   622             self error:'Missing moduleName'.
   622 	    self error:'Missing moduleName'.
   623         ].
   623 	].
   624         moduleNameUsed := owningClass theNonMetaclass libraryName asSymbol.
   624 	moduleNameUsed := owningClass theNonMetaclass libraryName asSymbol.
   625     ].
   625     ].
   626     moduleHandle isNil ifTrue:[
   626     moduleHandle isNil ifTrue:[
   627         handle := self loadLibrary:moduleNameUsed.
   627 	handle := self loadLibrary:moduleNameUsed.
   628         handle isNil ifTrue:[
   628 	handle isNil ifTrue:[
   629             self error:('Cannot find or load dll/module: "%1"' bindWith: moduleNameUsed).
   629 	    self error:('Cannot find or load dll/module: "%1"' bindWith: moduleNameUsed).
   630         ].
   630 	].
   631         moduleHandle := handle.
   631 	moduleHandle := handle.
   632     ].
   632     ].
   633     name isNumber ifFalse:[
   633     name isNumber ifFalse:[
   634         functionName := name.
   634 	functionName := name.
   635         (moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
   635 	(moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
   636             functionName := ('_', functionName) asSymbol.
   636 	    functionName := ('_', functionName) asSymbol.
   637 
   637 
   638             (moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
   638 	    (moduleHandle getFunctionAddress:functionName into:self) isNil ifTrue:[
   639                 moduleHandle := nil.
   639 		moduleHandle := nil.
   640                 self error:'Missing function: ', name, ' in module: ', moduleNameUsed.
   640 		self error:'Missing function: ', name, ' in module: ', moduleNameUsed.
   641             ].
   641 	    ].
   642         ].
   642 	].
   643     ].
   643     ].
   644 
   644 
   645     "Modified: / 10-04-2012 / 12:12:44 / cg"
   645     "Modified: / 10-04-2012 / 12:12:44 / cg"
   646 !
   646 !
   647 
   647 
   648 loadLibrary:dllName
   648 loadLibrary:dllName
   649     |handle nameString filename|
   649     |handle nameString filename|
   650 
   650 
   651     filename := dllName.
   651     filename := dllName.
   652     DllMapping notNil ifTrue:[
   652     DllMapping notNil ifTrue:[
   653         filename := DllMapping at:filename ifAbsent:[ filename ]
   653 	filename := DllMapping at:filename ifAbsent:[ filename ]
   654     ].
   654     ].
   655 
   655 
   656     filename := filename asFilename.
   656     filename := filename asFilename.
   657     nameString := filename name.
   657     nameString := filename name.
   658 
   658 
   659     "try to load, maybe the system knows where to find the dll"
   659     "try to load, maybe the system knows where to find the dll"
   660     handle := ObjectFileLoader loadDynamicObject:filename.
   660     handle := ObjectFileLoader loadDynamicObject:filename.
   661     handle notNil ifTrue:[^ handle ].
   661     handle notNil ifTrue:[^ handle ].
   662 
   662 
   663     filename isAbsolute ifFalse:[
   663     filename isAbsolute ifFalse:[
   664         "First ask the class defining the ExternalFunction for the location of the dlls ..."
   664 	"First ask the class defining the ExternalFunction for the location of the dlls ..."
   665         owningClass notNil ifTrue:[
   665 	owningClass notNil ifTrue:[
   666             owningClass dllPath do:[:eachDirectory |
   666 	    owningClass dllPath do:[:eachDirectory |
   667                 handle := ObjectFileLoader
   667 		handle := ObjectFileLoader
   668                             loadDynamicObject:(eachDirectory asFilename construct:nameString) pathName.
   668 			    loadDynamicObject:(eachDirectory asFilename construct:nameString) pathName.
   669                 handle notNil ifTrue:[^ handle ].
   669 		handle notNil ifTrue:[^ handle ].
   670             ].
   670 	    ].
   671         ].
   671 	].
   672         ".. then ask the system"
   672 	".. then ask the system"
   673         self class dllPath do:[:eachDirectory |
   673 	self class dllPath do:[:eachDirectory |
   674             handle := ObjectFileLoader
   674 	    handle := ObjectFileLoader
   675                         loadDynamicObject:(eachDirectory asFilename construct:nameString) pathName.
   675 			loadDynamicObject:(eachDirectory asFilename construct:nameString) pathName.
   676             handle notNil ifTrue:[^ handle ].
   676 	    handle notNil ifTrue:[^ handle ].
   677         ].
   677 	].
   678     ].
   678     ].
   679 
   679 
   680     filename suffix isEmpty ifTrue:[
   680     filename suffix isEmpty ifTrue:[
   681         "/ try again with the OS-specific dll-extension
   681 	"/ try again with the OS-specific dll-extension
   682         ^ self loadLibrary:(filename withSuffix:ObjectFileLoader sharedLibrarySuffix)
   682 	^ self loadLibrary:(filename withSuffix:ObjectFileLoader sharedLibrarySuffix)
   683     ].
   683     ].
   684 
   684 
   685     ^ nil
   685     ^ nil
   686 
   686 
   687     "Modified: / 10-04-2012 / 12:21:06 / cg"
   687     "Modified: / 10-04-2012 / 12:21:06 / cg"
   696 
   696 
   697 !ExternalLibraryFunction methodsFor:'private-accessing'!
   697 !ExternalLibraryFunction methodsFor:'private-accessing'!
   698 
   698 
   699 ffiTypeSymbolForType:aType
   699 ffiTypeSymbolForType:aType
   700     "map type to one of the ffi-supported ones:
   700     "map type to one of the ffi-supported ones:
   701         sint8, sint16, sint32, sint64
   701 	sint8, sint16, sint32, sint64
   702         uint8, uint16, uint32, uint64
   702 	uint8, uint16, uint32, uint64
   703         bool void pointer handle
   703 	bool void pointer handle
   704     "
   704     "
   705 
   705 
   706     aType == #sint8           ifTrue:[^ aType ].
   706     aType == #sint8           ifTrue:[^ aType ].
   707     aType == #sint16          ifTrue:[^ aType ].
   707     aType == #sint16          ifTrue:[^ aType ].
   708     aType == #sint32          ifTrue:[^ aType ].
   708     aType == #sint32          ifTrue:[^ aType ].
   758     aType == #structIn        ifTrue:[^ #pointer ].
   758     aType == #structIn        ifTrue:[^ #pointer ].
   759     aType == #structOut       ifTrue:[^ #pointer ].
   759     aType == #structOut       ifTrue:[^ #pointer ].
   760     aType == #unsigned        ifTrue:[^ #uint ].
   760     aType == #unsigned        ifTrue:[^ #uint ].
   761 
   761 
   762     (aType isString or:[aType isSymbol]) ifFalse:[
   762     (aType isString or:[aType isSymbol]) ifFalse:[
   763         CType isNil ifTrue:[
   763 	CType isNil ifTrue:[
   764             self error:'unknown type'.
   764 	    self error:'unknown type'.
   765         ].
   765 	].
   766         ^ aType typeSymbol.
   766 	^ aType typeSymbol.
   767     ].
   767     ].
   768 
   768 
   769     (aType endsWith:'*') ifTrue:[
   769     (aType endsWith:'*') ifTrue:[
   770         ^ #pointer.
   770 	^ #pointer.
   771     ].
   771     ].
   772     (aType endsWith:'Pointer') ifTrue:[
   772     (aType endsWith:'Pointer') ifTrue:[
   773         ^ #pointer.
   773 	^ #pointer.
   774     ].
   774     ].
   775     ^ aType
   775     ^ aType
   776 
   776 
   777     "Modified: / 14-06-2007 / 17:21:42 / cg"
   777     "Modified: / 14-06-2007 / 17:21:42 / cg"
   778 !
   778 !
   833     argTypeSymbols := argumentTypes.
   833     argTypeSymbols := argumentTypes.
   834     returnTypeSymbol := returnType.
   834     returnTypeSymbol := returnType.
   835 
   835 
   836     virtual := self isVirtualCPP.
   836     virtual := self isVirtualCPP.
   837     (virtual "or:[self isNonVirtualCPP]") ifTrue:[
   837     (virtual "or:[self isNonVirtualCPP]") ifTrue:[
   838         aCPlusPlusObjectOrNil isNil ifTrue:[
   838 	aCPlusPlusObjectOrNil isNil ifTrue:[
   839             "/ must have a c++ object instance
   839 	    "/ must have a c++ object instance
   840             self primitiveFailed.
   840 	    self primitiveFailed.
   841         ].
   841 	].
   842 
   842 
   843         "/ and it must be a kind of ExternalStructure !!
   843 	"/ and it must be a kind of ExternalStructure !!
   844         (aCPlusPlusObjectOrNil isKindOf:ExternalStructure) ifFalse:[
   844 	(aCPlusPlusObjectOrNil isKindOf:ExternalStructure) ifFalse:[
   845             self primitiveFailed.
   845 	    self primitiveFailed.
   846         ].
   846 	].
   847         virtual ifTrue:[
   847 	virtual ifTrue:[
   848             vtOffset := name.
   848 	    vtOffset := name.
   849             (vtOffset between:0 and:10000) ifFalse:[
   849 	    (vtOffset between:0 and:10000) ifFalse:[
   850                 self primitiveFailed.
   850 		self primitiveFailed.
   851             ]
   851 	    ]
   852         ].
   852 	].
   853     ] ifFalse:[
   853     ] ifFalse:[
   854         aCPlusPlusObjectOrNil notNil ifTrue:[
   854 	aCPlusPlusObjectOrNil notNil ifTrue:[
   855             "/ must NOT have a c++ object instance
   855 	    "/ must NOT have a c++ object instance
   856             self primitiveFailed.
   856 	    self primitiveFailed.
   857         ].
   857 	].
   858     ].
   858     ].
   859     async := self isAsync.
   859     async := self isAsync.
   860     unlimitedStack := self isUnlimitedStack.
   860     unlimitedStack := self isUnlimitedStack.
   861     callTypeNumber := self callTypeNumber.
   861     callTypeNumber := self callTypeNumber.
   862     "/ Transcript show:name; show:' async:'; showCR:async.
   862     "/ Transcript show:name; show:' async:'; showCR:async.
   874     ffi_type *__argTypesIncludingThis[MAX_ARGS+1];
   874     ffi_type *__argTypesIncludingThis[MAX_ARGS+1];
   875     ffi_type **__argTypes = __argTypesIncludingThis;
   875     ffi_type **__argTypes = __argTypesIncludingThis;
   876     ffi_type *__returnType = NULL;
   876     ffi_type *__returnType = NULL;
   877 
   877 
   878     union u {
   878     union u {
   879         int iVal;
   879 	int iVal;
   880         float fVal;
   880 	float fVal;
   881         double dVal;
   881 	double dVal;
   882         void *pointerVal;
   882 	void *pointerVal;
   883 # if defined(HAS_LONGLONG)
   883 # if defined(HAS_LONGLONG)
   884         long long longLongVal;
   884 	long long longLongVal;
   885 # else
   885 # else
   886 #  ifdef HAS_INT64
   886 #  ifdef HAS_INT64
   887         __int64__ longLongVal;
   887 	__int64__ longLongVal;
   888 #  else
   888 #  else
   889         struct ll { long low; long hi; } longLongVal;
   889 	struct ll { long low; long hi; } longLongVal;
   890 #  endif
   890 #  endif
   891 # endif
   891 # endif
   892     };
   892     };
   893     union u __argValuesIncludingThis[MAX_ARGS+1];
   893     union u __argValuesIncludingThis[MAX_ARGS+1];
   894     union u *__argValues = __argValuesIncludingThis;
   894     union u *__argValues = __argValuesIncludingThis;
   903     VOIDFUNC codeAddress = (VOIDFUNC)__INST(code_);
   903     VOIDFUNC codeAddress = (VOIDFUNC)__INST(code_);
   904     int __numArgsWanted;
   904     int __numArgsWanted;
   905 
   905 
   906 #   define __FAIL__(fcode) \
   906 #   define __FAIL__(fcode) \
   907     { \
   907     { \
   908         failureCode = fcode; goto getOutOfHere; \
   908 	failureCode = fcode; goto getOutOfHere; \
   909     }
   909     }
   910 
   910 
   911     if (argumentsOrNil == nil) {
   911     if (argumentsOrNil == nil) {
   912         __numArgs = 0;
   912 	__numArgs = 0;
   913     } else if (__isArray(argumentsOrNil)) {
   913     } else if (__isArray(argumentsOrNil)) {
   914         __numArgs = __arraySize(argumentsOrNil);
   914 	__numArgs = __arraySize(argumentsOrNil);
   915     } else {
   915     } else {
   916         __FAIL__(@symbol(BadArgumentVector))
   916 	__FAIL__(@symbol(BadArgumentVector))
   917     }
   917     }
   918     if (argTypeSymbols == nil) {
   918     if (argTypeSymbols == nil) {
   919         __numArgsWanted = 0;
   919 	__numArgsWanted = 0;
   920     } else if (__isArray(argTypeSymbols)) {
   920     } else if (__isArray(argTypeSymbols)) {
   921         __numArgsWanted = __arraySize(argTypeSymbols);
   921 	__numArgsWanted = __arraySize(argTypeSymbols);
   922     } else {
   922     } else {
   923         __FAIL__(@symbol(BadArgumentTypeVector))
   923 	__FAIL__(@symbol(BadArgumentTypeVector))
   924     }
   924     }
   925 
   925 
   926     if (__numArgs != __numArgsWanted) {
   926     if (__numArgs != __numArgsWanted) {
   927         __FAIL__(@symbol(ArgumentCountMismatch))
   927 	__FAIL__(@symbol(ArgumentCountMismatch))
   928     }
   928     }
   929     if (__numArgs > MAX_ARGS) {
   929     if (__numArgs > MAX_ARGS) {
   930         __FAIL__(@symbol(TooManyArguments))
   930 	__FAIL__(@symbol(TooManyArguments))
   931     }
   931     }
   932 
   932 
   933     /*
   933     /*
   934      * validate the return type
   934      * validate the return type
   935      */
   935      */
   936     __returnValuePointer = &__returnValue;
   936     __returnValuePointer = &__returnValue;
   937 
   937 
   938     if (returnTypeSymbol == @symbol(voidPointer)) {
   938     if (returnTypeSymbol == @symbol(voidPointer)) {
   939         returnTypeSymbol = @symbol(handle);
   939 	returnTypeSymbol = @symbol(handle);
   940     }
   940     }
   941 
   941 
   942     if (returnTypeSymbol == @symbol(int)) {
   942     if (returnTypeSymbol == @symbol(int)) {
   943         __returnType = __get_ffi_type_sint();
   943 	__returnType = __get_ffi_type_sint();
   944     } else if (returnTypeSymbol == @symbol(uint)) {
   944     } else if (returnTypeSymbol == @symbol(uint)) {
   945         __returnType = __get_ffi_type_uint();
   945 	__returnType = __get_ffi_type_uint();
   946     } else if (returnTypeSymbol == @symbol(uint8)) {
   946     } else if (returnTypeSymbol == @symbol(uint8)) {
   947         __returnType = __get_ffi_type_uint8();
   947 	__returnType = __get_ffi_type_uint8();
   948     } else if (returnTypeSymbol == @symbol(uint16)) {
   948     } else if (returnTypeSymbol == @symbol(uint16)) {
   949         __returnType = __get_ffi_type_uint16();
   949 	__returnType = __get_ffi_type_uint16();
   950     } else if (returnTypeSymbol == @symbol(uint32)) {
   950     } else if (returnTypeSymbol == @symbol(uint32)) {
   951         __returnType = __get_ffi_type_uint32();
   951 	__returnType = __get_ffi_type_uint32();
   952     } else if (returnTypeSymbol == @symbol(uint64)) {
   952     } else if (returnTypeSymbol == @symbol(uint64)) {
   953         __returnType = __get_ffi_type_uint64();
   953 	__returnType = __get_ffi_type_uint64();
   954 
   954 
   955     } else if (returnTypeSymbol == @symbol(sint)) {
   955     } else if (returnTypeSymbol == @symbol(sint)) {
   956         __returnType = __get_ffi_type_sint();
   956 	__returnType = __get_ffi_type_sint();
   957     } else if (returnTypeSymbol == @symbol(sint8)) {
   957     } else if (returnTypeSymbol == @symbol(sint8)) {
   958         __returnType = __get_ffi_type_sint8();
   958 	__returnType = __get_ffi_type_sint8();
   959     } else if (returnTypeSymbol == @symbol(sint16)) {
   959     } else if (returnTypeSymbol == @symbol(sint16)) {
   960         __returnType = __get_ffi_type_sint16();
   960 	__returnType = __get_ffi_type_sint16();
   961     } else if (returnTypeSymbol == @symbol(sint32)) {
   961     } else if (returnTypeSymbol == @symbol(sint32)) {
   962         __returnType = __get_ffi_type_sint32();
   962 	__returnType = __get_ffi_type_sint32();
   963     } else if (returnTypeSymbol == @symbol(sint64)) {
   963     } else if (returnTypeSymbol == @symbol(sint64)) {
   964         __returnType = __get_ffi_type_sint64();
   964 	__returnType = __get_ffi_type_sint64();
   965 
   965 
   966     } else if (returnTypeSymbol == @symbol(long)) {
   966     } else if (returnTypeSymbol == @symbol(long)) {
   967         if (sizeof(long) == 4) {
   967 	if (sizeof(long) == 4) {
   968            returnTypeSymbol = @symbol(sint32);
   968 	   returnTypeSymbol = @symbol(sint32);
   969            __returnType = __get_ffi_type_sint32();
   969 	   __returnType = __get_ffi_type_sint32();
   970         } else if (sizeof(long) == 8) {
   970 	} else if (sizeof(long) == 8) {
   971            returnTypeSymbol = @symbol(sint64);
   971 	   returnTypeSymbol = @symbol(sint64);
   972            __returnType = __get_ffi_type_sint64();
   972 	   __returnType = __get_ffi_type_sint64();
   973         } else {
   973 	} else {
   974             __FAIL__(@symbol(UnknownReturnType))
   974 	    __FAIL__(@symbol(UnknownReturnType))
   975         }
   975 	}
   976 
   976 
   977     } else if (returnTypeSymbol == @symbol(ulong)) {
   977     } else if (returnTypeSymbol == @symbol(ulong)) {
   978         if (sizeof(long) == 4) {
   978 	if (sizeof(long) == 4) {
   979            returnTypeSymbol = @symbol(uint32);
   979 	   returnTypeSymbol = @symbol(uint32);
   980            __returnType = __get_ffi_type_uint32();
   980 	   __returnType = __get_ffi_type_uint32();
   981         }else if (sizeof(long) == 8) {
   981 	}else if (sizeof(long) == 8) {
   982            returnTypeSymbol = @symbol(uint64);
   982 	   returnTypeSymbol = @symbol(uint64);
   983            __returnType = __get_ffi_type_uint64();
   983 	   __returnType = __get_ffi_type_uint64();
   984         } else {
   984 	} else {
   985             __FAIL__(@symbol(UnknownReturnType))
   985 	    __FAIL__(@symbol(UnknownReturnType))
   986         }
   986 	}
   987 
   987 
   988     } else if (returnTypeSymbol == @symbol(bool)) {
   988     } else if (returnTypeSymbol == @symbol(bool)) {
   989         __returnType = __get_ffi_type_uint();
   989 	__returnType = __get_ffi_type_uint();
   990 
   990 
   991     } else if (returnTypeSymbol == @symbol(float)) {
   991     } else if (returnTypeSymbol == @symbol(float)) {
   992         __returnType = __get_ffi_type_float();
   992 	__returnType = __get_ffi_type_float();
   993     } else if (returnTypeSymbol == @symbol(double)) {
   993     } else if (returnTypeSymbol == @symbol(double)) {
   994         __returnType = __get_ffi_type_double();
   994 	__returnType = __get_ffi_type_double();
   995 
   995 
   996     } else if (returnTypeSymbol == @symbol(void)) {
   996     } else if (returnTypeSymbol == @symbol(void)) {
   997         __returnType = __get_ffi_type_void();
   997 	__returnType = __get_ffi_type_void();
   998         __returnValuePointer = NULL;
   998 	__returnValuePointer = NULL;
   999     } else if ((returnTypeSymbol == @symbol(pointer))
   999     } else if ((returnTypeSymbol == @symbol(pointer))
  1000                || (returnTypeSymbol == @symbol(handle))
  1000 	       || (returnTypeSymbol == @symbol(handle))
  1001                || (returnTypeSymbol == @symbol(charPointer))
  1001 	       || (returnTypeSymbol == @symbol(charPointer))
  1002                || (returnTypeSymbol == @symbol(bytePointer))
  1002 	       || (returnTypeSymbol == @symbol(bytePointer))
  1003                || (returnTypeSymbol == @symbol(floatPointer))
  1003 	       || (returnTypeSymbol == @symbol(floatPointer))
  1004                || (returnTypeSymbol == @symbol(doublePointer))
  1004 	       || (returnTypeSymbol == @symbol(doublePointer))
  1005                || (returnTypeSymbol == @symbol(intPointer))
  1005 	       || (returnTypeSymbol == @symbol(intPointer))
  1006                || (returnTypeSymbol == @symbol(shortPointer))
  1006 	       || (returnTypeSymbol == @symbol(shortPointer))
  1007                || (returnTypeSymbol == @symbol(wcharPointer))) {
  1007 	       || (returnTypeSymbol == @symbol(wcharPointer))) {
  1008         __returnType = __get_ffi_type_pointer();
  1008 	__returnType = __get_ffi_type_pointer();
  1009     } else {
  1009     } else {
  1010         if (__isSymbol(returnTypeSymbol)
  1010 	if (__isSymbol(returnTypeSymbol)
  1011          && ((returnValueClass = __GLOBAL_GET(returnTypeSymbol)) != nil)) {
  1011 	 && ((returnValueClass = __GLOBAL_GET(returnTypeSymbol)) != nil)) {
  1012             if (! __isBehaviorLike(returnValueClass)) {
  1012 	    if (! __isBehaviorLike(returnValueClass)) {
  1013                 __FAIL__(@symbol(NonBehaviorReturnType))
  1013 		__FAIL__(@symbol(NonBehaviorReturnType))
  1014             }
  1014 	    }
  1015             if (! __qIsSubclassOfExternalAddress(returnValueClass)) {
  1015 	    if (! __qIsSubclassOfExternalAddress(returnValueClass)) {
  1016                 __FAIL__(@symbol(NonExternalAddressReturnType))
  1016 		__FAIL__(@symbol(NonExternalAddressReturnType))
  1017             }
  1017 	    }
  1018             __returnType = __get_ffi_type_pointer();
  1018 	    __returnType = __get_ffi_type_pointer();
  1019             returnTypeSymbol = @symbol(pointer);
  1019 	    returnTypeSymbol = @symbol(pointer);
  1020         } else {
  1020 	} else {
  1021             __FAIL__(@symbol(UnknownReturnType))
  1021 	    __FAIL__(@symbol(UnknownReturnType))
  1022         }
  1022 	}
  1023     }
  1023     }
  1024 
  1024 
  1025     /*
  1025     /*
  1026      * validate the c++ object
  1026      * validate the c++ object
  1027      */
  1027      */
  1028     if (aCPlusPlusObjectOrNil != nil) {
  1028     if (aCPlusPlusObjectOrNil != nil) {
  1029         struct cPlusPlusInstance {
  1029 	struct cPlusPlusInstance {
  1030             void **vTable;
  1030 	    void **vTable;
  1031         };
  1031 	};
  1032         struct cPlusPlusInstance *inst;
  1032 	struct cPlusPlusInstance *inst;
  1033 
  1033 
  1034         if (__isExternalAddressLike(aCPlusPlusObjectOrNil)) {
  1034 	if (__isExternalAddressLike(aCPlusPlusObjectOrNil)) {
  1035             inst = (void *)(__externalAddressVal(aCPlusPlusObjectOrNil));
  1035 	    inst = (void *)(__externalAddressVal(aCPlusPlusObjectOrNil));
  1036         } else if (__isExternalBytesLike(aCPlusPlusObjectOrNil)) {
  1036 	} else if (__isExternalBytesLike(aCPlusPlusObjectOrNil)) {
  1037             inst = (void *)(__externalBytesVal(aCPlusPlusObjectOrNil));
  1037 	    inst = (void *)(__externalBytesVal(aCPlusPlusObjectOrNil));
  1038         } else {
  1038 	} else {
  1039             __FAIL__(@symbol(InvalidInstance))
  1039 	    __FAIL__(@symbol(InvalidInstance))
  1040         }
  1040 	}
  1041         __argValues[0].pointerVal = inst;
  1041 	__argValues[0].pointerVal = inst;
  1042         __argValuePointersIncludingThis[0] = &(__argValues[0]);
  1042 	__argValuePointersIncludingThis[0] = &(__argValues[0]);
  1043         __argTypes[0] = __get_ffi_type_pointer();
  1043 	__argTypes[0] = __get_ffi_type_pointer();
  1044 
  1044 
  1045         __argValuePointers = &__argValuePointersIncludingThis[1];
  1045 	__argValuePointers = &__argValuePointersIncludingThis[1];
  1046         __argTypes = &__argTypesIncludingThis[1];
  1046 	__argTypes = &__argTypesIncludingThis[1];
  1047         __argValues = &__argValuesIncludingThis[1];
  1047 	__argValues = &__argValuesIncludingThis[1];
  1048         __numArgsIncludingThis = __numArgs + 1;
  1048 	__numArgsIncludingThis = __numArgs + 1;
  1049 
  1049 
  1050         if (virtual == true) {
  1050 	if (virtual == true) {
  1051             if (! __isSmallInteger(vtOffset)) {
  1051 	    if (! __isSmallInteger(vtOffset)) {
  1052                 __FAIL__(@symbol(InvalidVTableIndex))
  1052 		__FAIL__(@symbol(InvalidVTableIndex))
  1053             }
  1053 	    }
  1054             codeAddress = inst->vTable[__intVal(vtOffset)];
  1054 	    codeAddress = inst->vTable[__intVal(vtOffset)];
  1055 # ifdef VERBOSE
  1055 # ifdef VERBOSE
  1056             printf("virtual codeAddress: %x\n", codeAddress);
  1056 	    printf("virtual codeAddress: %x\n", codeAddress);
  1057 # endif
  1057 # endif
  1058         }
  1058 	}
  1059     } else {
  1059     } else {
  1060         __numArgsIncludingThis = __numArgs;
  1060 	__numArgsIncludingThis = __numArgs;
  1061 # ifdef VERBOSE
  1061 # ifdef VERBOSE
  1062         printf("codeAddress: %x\n", codeAddress);
  1062 	printf("codeAddress: %x\n", codeAddress);
  1063 # endif
  1063 # endif
  1064     }
  1064     }
  1065 
  1065 
  1066     /*
  1066     /*
  1067      * validate all arg types and setup arg-buffers
  1067      * validate all arg types and setup arg-buffers
  1068      */
  1068      */
  1069     for (i=0; i<__numArgs; i++) {
  1069     for (i=0; i<__numArgs; i++) {
  1070         ffi_type *thisType;
  1070 	ffi_type *thisType;
  1071         void *argValuePtr;
  1071 	void *argValuePtr;
  1072         OBJ typeSymbol;
  1072 	OBJ typeSymbol;
  1073         OBJ arg;
  1073 	OBJ arg;
  1074 
  1074 
  1075         failureInfo = __mkSmallInteger(i+1);   /* in case there is one */
  1075 	failureInfo = __mkSmallInteger(i+1);   /* in case there is one */
  1076 
  1076 
  1077         typeSymbol = __ArrayInstPtr(argTypeSymbols)->a_element[i];
  1077 	typeSymbol = __ArrayInstPtr(argTypeSymbols)->a_element[i];
  1078         arg = __ArrayInstPtr(argumentsOrNil)->a_element[i];
  1078 	arg = __ArrayInstPtr(argumentsOrNil)->a_element[i];
  1079 
  1079 
  1080         if (typeSymbol == @symbol(handle)) {
  1080 	if (typeSymbol == @symbol(handle)) {
  1081             typeSymbol = @symbol(pointer);
  1081 	    typeSymbol = @symbol(pointer);
  1082         } else if (typeSymbol == @symbol(voidPointer)) {
  1082 	} else if (typeSymbol == @symbol(voidPointer)) {
  1083             typeSymbol = @symbol(pointer);
  1083 	    typeSymbol = @symbol(pointer);
  1084         }
  1084 	}
  1085 
  1085 
  1086         if (typeSymbol == @symbol(long)) {
  1086 	if (typeSymbol == @symbol(long)) {
  1087             if (sizeof(long) == sizeof(int)) {
  1087 	    if (sizeof(long) == sizeof(int)) {
  1088                 typeSymbol = @symbol(sint);
  1088 		typeSymbol = @symbol(sint);
  1089             } else {
  1089 	    } else {
  1090                 if (sizeof(long) == 4) {
  1090 		if (sizeof(long) == 4) {
  1091                     typeSymbol = @symbol(sint32);
  1091 		    typeSymbol = @symbol(sint32);
  1092                 } else if (sizeof(long) == 8) {
  1092 		} else if (sizeof(long) == 8) {
  1093                     typeSymbol = @symbol(sint64);
  1093 		    typeSymbol = @symbol(sint64);
  1094                 }
  1094 		}
  1095             }
  1095 	    }
  1096         }
  1096 	}
  1097         if (typeSymbol == @symbol(ulong)) {
  1097 	if (typeSymbol == @symbol(ulong)) {
  1098             if (sizeof(unsigned long) == sizeof(unsigned int)) {
  1098 	    if (sizeof(unsigned long) == sizeof(unsigned int)) {
  1099                 typeSymbol = @symbol(uint);
  1099 		typeSymbol = @symbol(uint);
  1100             } else {
  1100 	    } else {
  1101                 if (sizeof(long) == 4) {
  1101 		if (sizeof(long) == 4) {
  1102                     typeSymbol = @symbol(uint32);
  1102 		    typeSymbol = @symbol(uint32);
  1103                 } else if (sizeof(long) == 8) {
  1103 		} else if (sizeof(long) == 8) {
  1104                     typeSymbol = @symbol(uint64);
  1104 		    typeSymbol = @symbol(uint64);
  1105                 }
  1105 		}
  1106             }
  1106 	    }
  1107         }
  1107 	}
  1108 
  1108 
  1109         if (typeSymbol == @symbol(int) || typeSymbol == @symbol(sint)) {
  1109 	if (typeSymbol == @symbol(int) || typeSymbol == @symbol(sint)) {
  1110             thisType = __get_ffi_type_sint();
  1110 	    thisType = __get_ffi_type_sint();
  1111             if (__isSmallInteger(arg)) {
  1111 	    if (__isSmallInteger(arg)) {
  1112                 __argValues[i].iVal = __intVal(arg);
  1112 		__argValues[i].iVal = __intVal(arg);
  1113             } else {
  1113 	    } else {
  1114                 __argValues[i].iVal = __signedLongIntVal(arg);
  1114 		__argValues[i].iVal = __signedLongIntVal(arg);
  1115                 if (__argValues[i].iVal == 0) {
  1115 		if (__argValues[i].iVal == 0) {
  1116                     __FAIL__(@symbol(InvalidArgument))
  1116 		    __FAIL__(@symbol(InvalidArgument))
  1117                 }
  1117 		}
  1118             }
  1118 	    }
  1119             argValuePtr = &(__argValues[i].iVal);
  1119 	    argValuePtr = &(__argValues[i].iVal);
  1120 
  1120 
  1121         } else if (typeSymbol == @symbol(uint)) {
  1121 	} else if (typeSymbol == @symbol(uint)) {
  1122             thisType = __get_ffi_type_uint();
  1122 	    thisType = __get_ffi_type_uint();
  1123 
  1123 
  1124             if (__isSmallInteger(arg)) {
  1124 	    if (__isSmallInteger(arg)) {
  1125                 __argValues[i].iVal = __intVal(arg);
  1125 		__argValues[i].iVal = __intVal(arg);
  1126             } else {
  1126 	    } else {
  1127                 __argValues[i].iVal = __unsignedLongIntVal(arg);
  1127 		__argValues[i].iVal = __unsignedLongIntVal(arg);
  1128                 if (__argValues[i].iVal == 0) {
  1128 		if (__argValues[i].iVal == 0) {
  1129                     __FAIL__(@symbol(InvalidArgument))
  1129 		    __FAIL__(@symbol(InvalidArgument))
  1130                 }
  1130 		}
  1131             }
  1131 	    }
  1132             argValuePtr = &(__argValues[i].iVal);
  1132 	    argValuePtr = &(__argValues[i].iVal);
  1133 
  1133 
  1134         } else if (typeSymbol == @symbol(uint8)) {
  1134 	} else if (typeSymbol == @symbol(uint8)) {
  1135             thisType = __get_ffi_type_uint8();
  1135 	    thisType = __get_ffi_type_uint8();
  1136             if (! __isSmallInteger(arg)) {
  1136 	    if (! __isSmallInteger(arg)) {
  1137                 __FAIL__(@symbol(InvalidArgument))
  1137 		__FAIL__(@symbol(InvalidArgument))
  1138             }
  1138 	    }
  1139             __argValues[i].iVal = __intVal(arg);
  1139 	    __argValues[i].iVal = __intVal(arg);
  1140             if (((unsigned)(__argValues[i].iVal)) > 0xFF) {
  1140 	    if (((unsigned)(__argValues[i].iVal)) > 0xFF) {
  1141                 __FAIL__(@symbol(InvalidArgument))
  1141 		__FAIL__(@symbol(InvalidArgument))
  1142             }
  1142 	    }
  1143             argValuePtr = &(__argValues[i].iVal);
  1143 	    argValuePtr = &(__argValues[i].iVal);
  1144 
  1144 
  1145         } else if (typeSymbol == @symbol(sint8)) {
  1145 	} else if (typeSymbol == @symbol(sint8)) {
  1146             thisType = __get_ffi_type_sint8();
  1146 	    thisType = __get_ffi_type_sint8();
  1147             if (! __isSmallInteger(arg)) {
  1147 	    if (! __isSmallInteger(arg)) {
  1148                 __FAIL__(@symbol(InvalidArgument))
  1148 		__FAIL__(@symbol(InvalidArgument))
  1149             }
  1149 	    }
  1150             __argValues[i].iVal = __intVal(arg);
  1150 	    __argValues[i].iVal = __intVal(arg);
  1151             if (((__argValues[i].iVal) < -0x80) || ((__argValues[i].iVal) > 0x7F))  {
  1151 	    if (((__argValues[i].iVal) < -0x80) || ((__argValues[i].iVal) > 0x7F))  {
  1152                 __FAIL__(@symbol(InvalidArgument))
  1152 		__FAIL__(@symbol(InvalidArgument))
  1153             }
  1153 	    }
  1154             argValuePtr = &(__argValues[i].iVal);
  1154 	    argValuePtr = &(__argValues[i].iVal);
  1155 
  1155 
  1156         } else if (typeSymbol == @symbol(uint16)) {
  1156 	} else if (typeSymbol == @symbol(uint16)) {
  1157             thisType = __get_ffi_type_uint16();
  1157 	    thisType = __get_ffi_type_uint16();
  1158             if (! __isSmallInteger(arg)) {
  1158 	    if (! __isSmallInteger(arg)) {
  1159                 __FAIL__(@symbol(InvalidArgument))
  1159 		__FAIL__(@symbol(InvalidArgument))
  1160             }
  1160 	    }
  1161             __argValues[i].iVal = __intVal(arg);
  1161 	    __argValues[i].iVal = __intVal(arg);
  1162             if (((unsigned)(__argValues[i].iVal)) > 0xFFFF) {
  1162 	    if (((unsigned)(__argValues[i].iVal)) > 0xFFFF) {
  1163                 __FAIL__(@symbol(InvalidArgument))
  1163 		__FAIL__(@symbol(InvalidArgument))
  1164             }
  1164 	    }
  1165             argValuePtr = &(__argValues[i].iVal);
  1165 	    argValuePtr = &(__argValues[i].iVal);
  1166 
  1166 
  1167         } else if (typeSymbol == @symbol(sint16)) {
  1167 	} else if (typeSymbol == @symbol(sint16)) {
  1168             thisType = __get_ffi_type_sint16();
  1168 	    thisType = __get_ffi_type_sint16();
  1169             if (! __isSmallInteger(arg)) {
  1169 	    if (! __isSmallInteger(arg)) {
  1170                 __FAIL__(@symbol(InvalidArgument))
  1170 		__FAIL__(@symbol(InvalidArgument))
  1171             }
  1171 	    }
  1172             __argValues[i].iVal = __intVal(arg);
  1172 	    __argValues[i].iVal = __intVal(arg);
  1173             if (((__argValues[i].iVal) < -0x8000) || ((__argValues[i].iVal) > 0x7FFF))  {
  1173 	    if (((__argValues[i].iVal) < -0x8000) || ((__argValues[i].iVal) > 0x7FFF))  {
  1174                 __FAIL__(@symbol(InvalidArgument))
  1174 		__FAIL__(@symbol(InvalidArgument))
  1175             }
  1175 	    }
  1176             argValuePtr = &(__argValues[i].iVal);
  1176 	    argValuePtr = &(__argValues[i].iVal);
  1177 
  1177 
  1178         } else if ((typeSymbol == @symbol(uint32)) || (typeSymbol == @symbol(sint32))) {
  1178 	} else if ((typeSymbol == @symbol(uint32)) || (typeSymbol == @symbol(sint32))) {
  1179             thisType = __get_ffi_type_uint32();
  1179 	    thisType = __get_ffi_type_uint32();
  1180             if (__isSmallInteger(arg)) {
  1180 	    if (__isSmallInteger(arg)) {
  1181                 __argValues[i].iVal = __intVal(arg);
  1181 		__argValues[i].iVal = __intVal(arg);
  1182             } else {
  1182 	    } else {
  1183                 __argValues[i].iVal = __unsignedLongIntVal(arg);
  1183 		__argValues[i].iVal = __unsignedLongIntVal(arg);
  1184                 if (__argValues[i].iVal == 0) {
  1184 		if (__argValues[i].iVal == 0) {
  1185                     __FAIL__(@symbol(InvalidArgument))
  1185 		    __FAIL__(@symbol(InvalidArgument))
  1186                 }
  1186 		}
  1187             }
  1187 	    }
  1188             argValuePtr = &(__argValues[i].iVal);
  1188 	    argValuePtr = &(__argValues[i].iVal);
  1189 
  1189 
  1190         } else if (typeSymbol == @symbol(float)) {
  1190 	} else if (typeSymbol == @symbol(float)) {
  1191             thisType = __get_ffi_type_float();
  1191 	    thisType = __get_ffi_type_float();
  1192             if (__isSmallInteger(arg)) {
  1192 	    if (__isSmallInteger(arg)) {
  1193                 __argValues[i].fVal = (float)(__intVal(arg));
  1193 		__argValues[i].fVal = (float)(__intVal(arg));
  1194             } else if (__isFloat(arg)) {
  1194 	    } else if (__isFloat(arg)) {
  1195                 __argValues[i].fVal = (float)(__floatVal(arg));
  1195 		__argValues[i].fVal = (float)(__floatVal(arg));
  1196             } else if (__isShortFloat(arg)) {
  1196 	    } else if (__isShortFloat(arg)) {
  1197                 __argValues[i].fVal = (float)(__shortFloatVal(arg));
  1197 		__argValues[i].fVal = (float)(__shortFloatVal(arg));
  1198             } else {
  1198 	    } else {
  1199                 __FAIL__(@symbol(InvalidArgument))
  1199 		__FAIL__(@symbol(InvalidArgument))
  1200             }
  1200 	    }
  1201             argValuePtr = &(__argValues[i].fVal);
  1201 	    argValuePtr = &(__argValues[i].fVal);
  1202 
  1202 
  1203         } else if (typeSymbol == @symbol(double)) {
  1203 	} else if (typeSymbol == @symbol(double)) {
  1204             thisType = __get_ffi_type_double();
  1204 	    thisType = __get_ffi_type_double();
  1205             if (__isSmallInteger(arg)) {
  1205 	    if (__isSmallInteger(arg)) {
  1206                 __argValues[i].dVal = (double)(__intVal(arg));
  1206 		__argValues[i].dVal = (double)(__intVal(arg));
  1207             } else if (__isFloat(arg)) {
  1207 	    } else if (__isFloat(arg)) {
  1208                 __argValues[i].dVal = (double)(__floatVal(arg));
  1208 		__argValues[i].dVal = (double)(__floatVal(arg));
  1209             } else if (__isShortFloat(arg)) {
  1209 	    } else if (__isShortFloat(arg)) {
  1210                 __argValues[i].dVal = (double)(__shortFloatVal(arg));
  1210 		__argValues[i].dVal = (double)(__shortFloatVal(arg));
  1211             } else {
  1211 	    } else {
  1212                 __FAIL__(@symbol(InvalidArgument))
  1212 		__FAIL__(@symbol(InvalidArgument))
  1213             }
  1213 	    }
  1214             argValuePtr = &(__argValues[i].dVal);
  1214 	    argValuePtr = &(__argValues[i].dVal);
  1215 
  1215 
  1216         } else if (typeSymbol == @symbol(void)) {
  1216 	} else if (typeSymbol == @symbol(void)) {
  1217             thisType = __get_ffi_type_void();
  1217 	    thisType = __get_ffi_type_void();
  1218             argValuePtr = &null;
  1218 	    argValuePtr = &null;
  1219 
  1219 
  1220         } else if (typeSymbol == @symbol(charPointer)) {
  1220 	} else if (typeSymbol == @symbol(charPointer)) {
  1221             thisType = __get_ffi_type_pointer();
  1221 	    thisType = __get_ffi_type_pointer();
  1222             if (__isStringLike(arg)) {
  1222 	    if (__isStringLike(arg)) {
  1223                 if (async == true) goto badArgForAsyncCall;
  1223 		if (async == true) goto badArgForAsyncCall;
  1224                 __argValues[i].pointerVal = (void *)(__stringVal(arg));
  1224 		__argValues[i].pointerVal = (void *)(__stringVal(arg));
  1225             } else if (__isBytes(arg)) {
  1225 	    } else if (__isBytes(arg)) {
  1226                 if (async == true) goto badArgForAsyncCall;
  1226 		if (async == true) goto badArgForAsyncCall;
  1227                 __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1227 		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1228             } else if (__isExternalAddressLike(arg)) {
  1228 	    } else if (__isExternalAddressLike(arg)) {
  1229                 __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1229 		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1230             } else if (__isExternalBytesLike(arg)) {
  1230 	    } else if (__isExternalBytesLike(arg)) {
  1231                 __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1231 		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1232             } else {
  1232 	    } else {
  1233                 if (arg == nil) {
  1233 		if (arg == nil) {
  1234                     __argValues[i].pointerVal = (void *)0;
  1234 		    __argValues[i].pointerVal = (void *)0;
  1235                 } else {
  1235 		} else {
  1236                     __FAIL__(@symbol(InvalidArgument))
  1236 		    __FAIL__(@symbol(InvalidArgument))
  1237                 }
  1237 		}
  1238             }
  1238 	    }
  1239             argValuePtr = &(__argValues[i].pointerVal);;
  1239 	    argValuePtr = &(__argValues[i].pointerVal);;
  1240 
  1240 
  1241         } else if (typeSymbol == @symbol(wcharPointer)) {
  1241 	} else if (typeSymbol == @symbol(wcharPointer)) {
  1242             thisType = __get_ffi_type_pointer();
  1242 	    thisType = __get_ffi_type_pointer();
  1243             if (__isUnicode16String(arg)) {
  1243 	    if (__isUnicode16String(arg)) {
  1244                 if (async == true) goto badArgForAsyncCall;
  1244 		if (async == true) goto badArgForAsyncCall;
  1245                 __argValues[i].pointerVal = (void *)(__unicode16StringVal(arg));
  1245 		__argValues[i].pointerVal = (void *)(__unicode16StringVal(arg));
  1246             } else if (__isBytes(arg)) {
  1246 	    } else if (__isBytes(arg)) {
  1247                 if (async == true) goto badArgForAsyncCall;
  1247 		if (async == true) goto badArgForAsyncCall;
  1248                 __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1248 		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1249             } else if (__isExternalAddressLike(arg)) {
  1249 	    } else if (__isExternalAddressLike(arg)) {
  1250                 __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1250 		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1251             } else if (__isExternalBytesLike(arg)) {
  1251 	    } else if (__isExternalBytesLike(arg)) {
  1252                 __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1252 		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1253             } else {
  1253 	    } else {
  1254                 if (arg == nil) {
  1254 		if (arg == nil) {
  1255                     __argValues[i].pointerVal = (void *)0;
  1255 		    __argValues[i].pointerVal = (void *)0;
  1256                 } else {
  1256 		} else {
  1257                     __FAIL__(@symbol(InvalidArgument))
  1257 		    __FAIL__(@symbol(InvalidArgument))
  1258                 }
  1258 		}
  1259             }
  1259 	    }
  1260             argValuePtr = &(__argValues[i].pointerVal);;
  1260 	    argValuePtr = &(__argValues[i].pointerVal);;
  1261 
  1261 
  1262         } else if (typeSymbol == @symbol(floatPointer)) {
  1262 	} else if (typeSymbol == @symbol(floatPointer)) {
  1263             thisType = __get_ffi_type_pointer();
  1263 	    thisType = __get_ffi_type_pointer();
  1264             if (__isBytes(arg)) {
  1264 	    if (__isBytes(arg)) {
  1265                 if (async == true) goto badArgForAsyncCall;
  1265 		if (async == true) goto badArgForAsyncCall;
  1266                 __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1266 		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1267             } else if (__isExternalAddressLike(arg)) {
  1267 	    } else if (__isExternalAddressLike(arg)) {
  1268                 __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1268 		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1269             } else if (__isExternalBytesLike(arg)) {
  1269 	    } else if (__isExternalBytesLike(arg)) {
  1270                 __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1270 		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1271             } else if (__isFloats(arg)) {
  1271 	    } else if (__isFloats(arg)) {
  1272                 char *p = (char *)(__FloatArrayInstPtr(arg)->f_element);
  1272 		char *p = (char *)(__FloatArrayInstPtr(arg)->f_element);
  1273                 int nInstBytes;
  1273 		int nInstBytes;
  1274                 OBJ cls;
  1274 		OBJ cls;
  1275 
  1275 
  1276                 if (async == true) goto badArgForAsyncCall;
  1276 		if (async == true) goto badArgForAsyncCall;
  1277                 cls = __qClass(arg);
  1277 		cls = __qClass(arg);
  1278                 nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
  1278 		nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
  1279                 p = p + nInstBytes;
  1279 		p = p + nInstBytes;
  1280                 __argValues[i].pointerVal = p;
  1280 		__argValues[i].pointerVal = p;
  1281             } else {
  1281 	    } else {
  1282                 if (arg == nil) {
  1282 		if (arg == nil) {
  1283                     __argValues[i].pointerVal = (void *)0;
  1283 		    __argValues[i].pointerVal = (void *)0;
  1284                 } else {
  1284 		} else {
  1285                     __FAIL__(@symbol(InvalidArgument))
  1285 		    __FAIL__(@symbol(InvalidArgument))
  1286                 }
  1286 		}
  1287             }
  1287 	    }
  1288             argValuePtr = &(__argValues[i].pointerVal);;
  1288 	    argValuePtr = &(__argValues[i].pointerVal);;
  1289 
  1289 
  1290         } else if (typeSymbol == @symbol(doublePointer)) {
  1290 	} else if (typeSymbol == @symbol(doublePointer)) {
  1291             thisType = __get_ffi_type_pointer();
  1291 	    thisType = __get_ffi_type_pointer();
  1292             if (__isBytes(arg)) {
  1292 	    if (__isBytes(arg)) {
  1293                 if (async == true) goto badArgForAsyncCall;
  1293 		if (async == true) goto badArgForAsyncCall;
  1294                 __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1294 		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1295             } else if (__isExternalAddressLike(arg)) {
  1295 	    } else if (__isExternalAddressLike(arg)) {
  1296                 __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1296 		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1297             } else if (__isExternalBytesLike(arg)) {
  1297 	    } else if (__isExternalBytesLike(arg)) {
  1298                 __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1298 		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1299             } else if (__isDoubles(arg)) {
  1299 	    } else if (__isDoubles(arg)) {
  1300                 char *p = (char *)(__DoubleArrayInstPtr(arg)->d_element);
  1300 		char *p = (char *)(__DoubleArrayInstPtr(arg)->d_element);
  1301                 int nInstBytes;
  1301 		int nInstBytes;
  1302                 OBJ cls;
  1302 		OBJ cls;
  1303 
  1303 
  1304                 if (async == true) goto badArgForAsyncCall;
  1304 		if (async == true) goto badArgForAsyncCall;
  1305                 cls = __qClass(arg);
  1305 		cls = __qClass(arg);
  1306                 nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
  1306 		nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
  1307                 p = p + nInstBytes;
  1307 		p = p + nInstBytes;
  1308 # ifdef __NEED_DOUBLE_ALIGN
  1308 # ifdef __NEED_DOUBLE_ALIGN
  1309                 if ((INT)pFirst & (__DOUBLE_ALIGN-1)) {
  1309 		if ((INT)(__DoubleArrayInstPtr(arg)->d_element) & (__DOUBLE_ALIGN-1)) {
  1310                     int delta = __DOUBLE_ALIGN - ((INT)p & (__DOUBLE_ALIGN-1));
  1310 		    int delta = __DOUBLE_ALIGN - ((INT)p & (__DOUBLE_ALIGN-1));
  1311 
  1311 
  1312                     p += delta;
  1312 		    p += delta;
  1313                 }
  1313 		}
  1314 # endif
  1314 # endif
  1315                 __argValues[i].pointerVal = p;
  1315 		__argValues[i].pointerVal = p;
  1316             } else {
  1316 	    } else {
  1317                 if (arg == nil) {
  1317 		if (arg == nil) {
  1318                     __argValues[i].pointerVal = (void *)0;
  1318 		    __argValues[i].pointerVal = (void *)0;
  1319                 } else {
  1319 		} else {
  1320                     __FAIL__(@symbol(InvalidArgument))
  1320 		    __FAIL__(@symbol(InvalidArgument))
  1321                 }
  1321 		}
  1322             }
  1322 	    }
  1323             argValuePtr = &(__argValues[i].pointerVal);;
  1323 	    argValuePtr = &(__argValues[i].pointerVal);;
  1324 
  1324 
  1325         } else if (typeSymbol == @symbol(pointer)) {
  1325 	} else if (typeSymbol == @symbol(pointer)) {
  1326 commonPointerTypeArg: ;
  1326 commonPointerTypeArg: ;
  1327             thisType = __get_ffi_type_pointer();
  1327 	    thisType = __get_ffi_type_pointer();
  1328             if (arg == nil) {
  1328 	    if (arg == nil) {
  1329                 __argValues[i].pointerVal = NULL;
  1329 		__argValues[i].pointerVal = NULL;
  1330             } else if (__isExternalAddressLike(arg)) {
  1330 	    } else if (__isExternalAddressLike(arg)) {
  1331                 __argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1331 		__argValues[i].pointerVal = (void *)(__externalAddressVal(arg));
  1332             } else if (__isExternalBytesLike(arg)) {
  1332 	    } else if (__isExternalBytesLike(arg)) {
  1333                 __argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1333 		__argValues[i].pointerVal = (void *)(__externalBytesVal(arg));
  1334             } else if (__isByteArrayLike(arg)) {
  1334 	    } else if (__isByteArrayLike(arg)) {
  1335                 if (async == true) goto badArgForAsyncCall;
  1335 		if (async == true) goto badArgForAsyncCall;
  1336                 __argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1336 		__argValues[i].pointerVal = (void *)(__byteArrayVal(arg));
  1337             } else if (__isWordArray(arg) || __isSignedWordArray(arg)
  1337 	    } else if (__isWordArray(arg) || __isSignedWordArray(arg)
  1338                     || __isIntegerArray(arg) || __isSignedIntegerArray(arg)) {
  1338 		    || __isIntegerArray(arg) || __isSignedIntegerArray(arg)) {
  1339                 if (async == true) goto badArgForAsyncCall;
  1339 		if (async == true) goto badArgForAsyncCall;
  1340                 __argValues[i].pointerVal = (void *)(__integerArrayVal(arg));
  1340 		__argValues[i].pointerVal = (void *)(__integerArrayVal(arg));
  1341             } else if (__isFloatArray(arg)) {
  1341 	    } else if (__isFloatArray(arg)) {
  1342                 if (async == true) goto badArgForAsyncCall;
  1342 		if (async == true) goto badArgForAsyncCall;
  1343                 __argValues[i].pointerVal = (void *)(__FloatArrayInstPtr(arg)->f_element);
  1343 		__argValues[i].pointerVal = (void *)(__FloatArrayInstPtr(arg)->f_element);
  1344             } else if (__isDoubleArray(arg)) {
  1344 	    } else if (__isDoubleArray(arg)) {
  1345                 if (async == true) goto badArgForAsyncCall;
  1345 		if (async == true) goto badArgForAsyncCall;
  1346                 __argValues[i].pointerVal = (void *)(__DoubleArrayInstPtr(arg)->d_element);
  1346 		__argValues[i].pointerVal = (void *)(__DoubleArrayInstPtr(arg)->d_element);
  1347             } else if (__isStringLike(arg)) {
  1347 	    } else if (__isStringLike(arg)) {
  1348                 if (async == true) {
  1348 		if (async == true) {
  1349 badArgForAsyncCall: ;
  1349 badArgForAsyncCall: ;
  1350                     __FAIL__(@symbol(BadArgForAsyncCall))
  1350 		    __FAIL__(@symbol(BadArgForAsyncCall))
  1351                 }
  1351 		}
  1352                 __argValues[i].pointerVal = (void *)(__stringVal(arg));
  1352 		__argValues[i].pointerVal = (void *)(__stringVal(arg));
  1353             } else if (__isBytes(arg) || __isWords(arg) || __isLongs(arg)) {
  1353 	    } else if (__isBytes(arg) || __isWords(arg) || __isLongs(arg)) {
  1354                 char *p = (char *)(__byteArrayVal(arg));
  1354 		char *p = (char *)(__byteArrayVal(arg));
  1355                 int nInstBytes;
  1355 		int nInstBytes;
  1356                 OBJ cls;
  1356 		OBJ cls;
  1357 
  1357 
  1358                 if (async == true) goto badArgForAsyncCall;
  1358 		if (async == true) goto badArgForAsyncCall;
  1359                 cls = __qClass(arg);
  1359 		cls = __qClass(arg);
  1360                 nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
  1360 		nInstBytes = __OBJS2BYTES__(__intVal(__ClassInstPtr(cls)->c_ninstvars));
  1361                 __argValues[i].pointerVal = p + nInstBytes;
  1361 		__argValues[i].pointerVal = p + nInstBytes;
  1362             } else {
  1362 	    } else {
  1363                 __FAIL__(@symbol(InvalidArgument))
  1363 		__FAIL__(@symbol(InvalidArgument))
  1364             }
  1364 	    }
  1365             argValuePtr = &(__argValues[i].pointerVal);;
  1365 	    argValuePtr = &(__argValues[i].pointerVal);;
  1366 
  1366 
  1367         } else if (typeSymbol == @symbol(bool)) {
  1367 	} else if (typeSymbol == @symbol(bool)) {
  1368             thisType = __get_ffi_type_uint();
  1368 	    thisType = __get_ffi_type_uint();
  1369 
  1369 
  1370             if (arg == true) {
  1370 	    if (arg == true) {
  1371                 __argValues[i].iVal = 1;
  1371 		__argValues[i].iVal = 1;
  1372             } else if (arg == false) {
  1372 	    } else if (arg == false) {
  1373                 __argValues[i].iVal = 0;
  1373 		__argValues[i].iVal = 0;
  1374             } else if (__isSmallInteger(arg)) {
  1374 	    } else if (__isSmallInteger(arg)) {
  1375                 __argValues[i].iVal = __intVal(arg);
  1375 		__argValues[i].iVal = __intVal(arg);
  1376             } else {
  1376 	    } else {
  1377                 __argValues[i].iVal = __unsignedLongIntVal(arg);
  1377 		__argValues[i].iVal = __unsignedLongIntVal(arg);
  1378                 if (__argValues[i].iVal == 0) {
  1378 		if (__argValues[i].iVal == 0) {
  1379                     __FAIL__(@symbol(InvalidArgument))
  1379 		    __FAIL__(@symbol(InvalidArgument))
  1380                 }
  1380 		}
  1381             }
  1381 	    }
  1382             argValuePtr = &(__argValues[i].iVal);
  1382 	    argValuePtr = &(__argValues[i].iVal);
  1383         } else {
  1383 	} else {
  1384             if (__isSymbol(typeSymbol)
  1384 	    if (__isSymbol(typeSymbol)
  1385              && ((argValueClass = __GLOBAL_GET(typeSymbol)) != nil)) {
  1385 	     && ((argValueClass = __GLOBAL_GET(typeSymbol)) != nil)) {
  1386                 if (! __isBehaviorLike(argValueClass)) {
  1386 		if (! __isBehaviorLike(argValueClass)) {
  1387                     __FAIL__(@symbol(NonBehaviorArgumentType))
  1387 		    __FAIL__(@symbol(NonBehaviorArgumentType))
  1388                 }
  1388 		}
  1389                 if (! __qIsSubclassOfExternalAddress(argValueClass)) {
  1389 		if (! __qIsSubclassOfExternalAddress(argValueClass)) {
  1390                     __FAIL__(@symbol(NonExternalAddressArgumentType))
  1390 		    __FAIL__(@symbol(NonExternalAddressArgumentType))
  1391                 }
  1391 		}
  1392                 goto commonPointerTypeArg; /* sorry */
  1392 		goto commonPointerTypeArg; /* sorry */
  1393             } else {
  1393 	    } else {
  1394                 __FAIL__(@symbol(UnknownArgumentType))
  1394 		__FAIL__(@symbol(UnknownArgumentType))
  1395             }
  1395 	    }
  1396         }
  1396 	}
  1397 
  1397 
  1398         __argTypes[i] = thisType;
  1398 	__argTypes[i] = thisType;
  1399         __argValuePointers[i] = argValuePtr;
  1399 	__argValuePointers[i] = argValuePtr;
  1400 
  1400 
  1401 # ifdef VERBOSE
  1401 # ifdef VERBOSE
  1402         printf("arg%d: %x\n", i, __argValues[i].iVal);
  1402 	printf("arg%d: %x\n", i, __argValues[i].iVal);
  1403 # endif
  1403 # endif
  1404     }
  1404     }
  1405     failureInfo = nil;
  1405     failureInfo = nil;
  1406 
  1406 
  1407     __callType = FFI_DEFAULT_ABI;
  1407     __callType = FFI_DEFAULT_ABI;
  1408 
  1408 
  1409 # ifdef CALLTYPE_FFI_STDCALL
  1409 # ifdef CALLTYPE_FFI_STDCALL
  1410     if (callTypeNumber == @global(CALLTYPE_API)) {
  1410     if (callTypeNumber == @global(CALLTYPE_API)) {
  1411         __callType = CALLTYPE_FFI_STDCALL;
  1411 	__callType = CALLTYPE_FFI_STDCALL;
  1412     }
  1412     }
  1413 # endif
  1413 # endif
  1414 # ifdef CALLTYPE_FFI_V8
  1414 # ifdef CALLTYPE_FFI_V8
  1415     if (callTypeNumber == @global(CALLTYPE_V8)) {
  1415     if (callTypeNumber == @global(CALLTYPE_V8)) {
  1416         __callType = CALLTYPE_FFI_V8;
  1416 	__callType = CALLTYPE_FFI_V8;
  1417     }
  1417     }
  1418 # endif
  1418 # endif
  1419 # ifdef CALLTYPE_FFI_V9
  1419 # ifdef CALLTYPE_FFI_V9
  1420     if (callTypeNumber == @global(CALLTYPE_V9)) {
  1420     if (callTypeNumber == @global(CALLTYPE_V9)) {
  1421         __callType = CALLTYPE_FFI_V9;
  1421 	__callType = CALLTYPE_FFI_V9;
  1422     }
  1422     }
  1423 # endif
  1423 # endif
  1424 # ifdef CALLTYPE_FFI_UNIX64
  1424 # ifdef CALLTYPE_FFI_UNIX64
  1425     if (callTypeNumber == @global(CALLTYPE_UNIX64)) {
  1425     if (callTypeNumber == @global(CALLTYPE_UNIX64)) {
  1426         __callType = CALLTYPE_FFI_UNIX64;
  1426 	__callType = CALLTYPE_FFI_UNIX64;
  1427     }
  1427     }
  1428 # endif
  1428 # endif
  1429 
  1429 
  1430     if (ffi_prep_cif(&__cif, __callType, __numArgsIncludingThis, __returnType, __argTypesIncludingThis) != FFI_OK) {
  1430     if (ffi_prep_cif(&__cif, __callType, __numArgsIncludingThis, __returnType, __argTypesIncludingThis) != FFI_OK) {
  1431         __FAIL__(@symbol(FFIPrepareFailed))
  1431 	__FAIL__(@symbol(FFIPrepareFailed))
  1432     }
  1432     }
  1433     if (async == true) {
  1433     if (async == true) {
  1434 # ifdef VERBOSE
  1434 # ifdef VERBOSE
  1435         printf("async call 0x%x\n", codeAddress);
  1435 	printf("async call 0x%x\n", codeAddress);
  1436 # endif
  1436 # endif
  1437 # ifdef WIN32
  1437 # ifdef WIN32
  1438         __STX_C_CALL4( "ffi_call", ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1438 	__STX_C_CALL4( "ffi_call", ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1439 # else
  1439 # else
  1440         __BEGIN_INTERRUPTABLE__
  1440 	__BEGIN_INTERRUPTABLE__
  1441         ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1441 	ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1442         __END_INTERRUPTABLE__
  1442 	__END_INTERRUPTABLE__
  1443 # endif
  1443 # endif
  1444     } else {
  1444     } else {
  1445         if (unlimitedStack == true) {
  1445 	if (unlimitedStack == true) {
  1446 # ifdef VERBOSE
  1446 # ifdef VERBOSE
  1447             printf("UNLIMITEDSTACKCALL call 0x%x\n", codeAddress);
  1447 	    printf("UNLIMITEDSTACKCALL call 0x%x\n", codeAddress);
  1448 # endif
  1448 # endif
  1449 # if 0
  1449 # if 0
  1450             __UNLIMITEDSTACKCALL__(ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1450 	    __UNLIMITEDSTACKCALL__(ffi_call, &__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1451 # endif
  1451 # endif
  1452         } else {
  1452 	} else {
  1453 # ifdef VERBOSE
  1453 # ifdef VERBOSE
  1454             printf("call 0x%x\n", codeAddress);
  1454 	    printf("call 0x%x\n", codeAddress);
  1455 # endif
  1455 # endif
  1456             ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1456 	    ffi_call(&__cif, codeAddress, __returnValuePointer, __argValuePointersIncludingThis);
  1457         }
  1457 	}
  1458     }
  1458     }
  1459 # ifdef VERBOSE
  1459 # ifdef VERBOSE
  1460     printf("retval is %d (0x%x)\n", __returnValue.iVal, __returnValue.iVal);
  1460     printf("retval is %d (0x%x)\n", __returnValue.iVal, __returnValue.iVal);
  1461 # endif
  1461 # endif
  1462     if ((returnTypeSymbol == @symbol(int))
  1462     if ((returnTypeSymbol == @symbol(int))
  1463      || (returnTypeSymbol == @symbol(sint))
  1463      || (returnTypeSymbol == @symbol(sint))
  1464      || (returnTypeSymbol == @symbol(sint8))
  1464      || (returnTypeSymbol == @symbol(sint8))
  1465      || (returnTypeSymbol == @symbol(sint16))
  1465      || (returnTypeSymbol == @symbol(sint16))
  1466      || (returnTypeSymbol == @symbol(sint32))) {
  1466      || (returnTypeSymbol == @symbol(sint32))) {
  1467         RETURN ( __MKINT(__returnValue.iVal) );
  1467 	RETURN ( __MKINT(__returnValue.iVal) );
  1468     }
  1468     }
  1469     if ((returnTypeSymbol == @symbol(uint))
  1469     if ((returnTypeSymbol == @symbol(uint))
  1470      || (returnTypeSymbol == @symbol(uint8))
  1470      || (returnTypeSymbol == @symbol(uint8))
  1471      || (returnTypeSymbol == @symbol(uint16))
  1471      || (returnTypeSymbol == @symbol(uint16))
  1472      || (returnTypeSymbol == @symbol(uint32))) {
  1472      || (returnTypeSymbol == @symbol(uint32))) {
  1473         RETURN ( __MKUINT(__returnValue.iVal) );
  1473 	RETURN ( __MKUINT(__returnValue.iVal) );
  1474     }
  1474     }
  1475     if (returnTypeSymbol == @symbol(bool)) {
  1475     if (returnTypeSymbol == @symbol(bool)) {
  1476         RETURN ( __returnValue.iVal ? true : false );
  1476 	RETURN ( __returnValue.iVal ? true : false );
  1477     }
  1477     }
  1478     if (returnTypeSymbol == @symbol(float)) {
  1478     if (returnTypeSymbol == @symbol(float)) {
  1479         RETURN ( __MKFLOAT(__returnValue.fVal ));
  1479 	RETURN ( __MKFLOAT(__returnValue.fVal ));
  1480     }
  1480     }
  1481     if (returnTypeSymbol == @symbol(double)) {
  1481     if (returnTypeSymbol == @symbol(double)) {
  1482         RETURN ( __MKFLOAT(__returnValue.dVal ));
  1482 	RETURN ( __MKFLOAT(__returnValue.dVal ));
  1483     }
  1483     }
  1484     if (returnTypeSymbol == @symbol(void)) {
  1484     if (returnTypeSymbol == @symbol(void)) {
  1485         RETURN ( nil );
  1485 	RETURN ( nil );
  1486     }
  1486     }
  1487     if (returnTypeSymbol == @symbol(char)) {
  1487     if (returnTypeSymbol == @symbol(char)) {
  1488         RETURN ( __MKCHARACTER(__returnValue.iVal & 0xFF) );
  1488 	RETURN ( __MKCHARACTER(__returnValue.iVal & 0xFF) );
  1489     }
  1489     }
  1490     if (returnTypeSymbol == @symbol(wchar)) {
  1490     if (returnTypeSymbol == @symbol(wchar)) {
  1491         RETURN ( __MKUCHARACTER(__returnValue.iVal & 0xFFFF) );
  1491 	RETURN ( __MKUCHARACTER(__returnValue.iVal & 0xFFFF) );
  1492     }
  1492     }
  1493     if (returnTypeSymbol == @symbol(sint64)) {
  1493     if (returnTypeSymbol == @symbol(sint64)) {
  1494         RETURN ( __MKINT64(&__returnValue.longLongVal) );
  1494 	RETURN ( __MKINT64(&__returnValue.longLongVal) );
  1495     }
  1495     }
  1496     if (returnTypeSymbol == @symbol(uint64)) {
  1496     if (returnTypeSymbol == @symbol(uint64)) {
  1497         RETURN ( __MKUINT64(&__returnValue.longLongVal) );
  1497 	RETURN ( __MKUINT64(&__returnValue.longLongVal) );
  1498     }
  1498     }
  1499 
  1499 
  1500 # ifdef VERBOSE
  1500 # ifdef VERBOSE
  1501     printf("%x\n", __returnValue.pointerVal);
  1501     printf("%x\n", __returnValue.pointerVal);
  1502 # endif
  1502 # endif
  1503     if (returnTypeSymbol == @symbol(handle)) {
  1503     if (returnTypeSymbol == @symbol(handle)) {
  1504         returnValue = __MKEXTERNALADDRESS(__returnValue.pointerVal);
  1504 	returnValue = __MKEXTERNALADDRESS(__returnValue.pointerVal);
  1505     } else if (returnTypeSymbol == @symbol(pointer)) {
  1505     } else if (returnTypeSymbol == @symbol(pointer)) {
  1506         returnValue = __MKEXTERNALBYTES(__returnValue.pointerVal);
  1506 	returnValue = __MKEXTERNALBYTES(__returnValue.pointerVal);
  1507     } else if (returnTypeSymbol == @symbol(bytePointer)) {
  1507     } else if (returnTypeSymbol == @symbol(bytePointer)) {
  1508         returnValue = __MKEXTERNALBYTES(__returnValue.pointerVal);
  1508 	returnValue = __MKEXTERNALBYTES(__returnValue.pointerVal);
  1509     } else if (returnTypeSymbol == @symbol(charPointer)) {
  1509     } else if (returnTypeSymbol == @symbol(charPointer)) {
  1510         returnValue = __MKSTRING(__returnValue.pointerVal);
  1510 	returnValue = __MKSTRING(__returnValue.pointerVal);
  1511     } else if (returnTypeSymbol == @symbol(wcharPointer)) {
  1511     } else if (returnTypeSymbol == @symbol(wcharPointer)) {
  1512         returnValue = __MKU16STRING(__returnValue.pointerVal);
  1512 	returnValue = __MKU16STRING(__returnValue.pointerVal);
  1513     } else {
  1513     } else {
  1514         __FAIL__(@symbol(UnknownReturnType2))
  1514 	__FAIL__(@symbol(UnknownReturnType2))
  1515     }
  1515     }
  1516 #else /* no FFI support */
  1516 #else /* no FFI support */
  1517     failureCode = @symbol(FFINotSupported);
  1517     failureCode = @symbol(FFINotSupported);
  1518 #endif /* HAVE_FFI */
  1518 #endif /* HAVE_FFI */
  1519 getOutOfHere: ;
  1519 getOutOfHere: ;
  1520 %}.
  1520 %}.
  1521     failureCode notNil ifTrue:[
  1521     failureCode notNil ifTrue:[
  1522         (failureCode == #UnknownReturnType or:[ failureCode == #UnknownArgumentType ]) ifTrue:[
  1522 	(failureCode == #UnknownReturnType or:[ failureCode == #UnknownArgumentType ]) ifTrue:[
  1523             oldReturnType := returnType.
  1523 	    oldReturnType := returnType.
  1524             oldArgumentTypes := argumentTypes.
  1524 	    oldArgumentTypes := argumentTypes.
  1525             self adjustTypes.
  1525 	    self adjustTypes.
  1526             ((oldReturnType ~= returnType) or:[oldArgumentTypes ~= argumentTypes]) ifTrue:[
  1526 	    ((oldReturnType ~= returnType) or:[oldArgumentTypes ~= argumentTypes]) ifTrue:[
  1527                 thisContext restart
  1527 		thisContext restart
  1528             ].
  1528 	    ].
  1529         ].
  1529 	].
  1530         (failureCode == #BadArgForAsyncCall) ifTrue:[
  1530 	(failureCode == #BadArgForAsyncCall) ifTrue:[
  1531             ^ self tryAgainWithAsyncSafeArguments:argumentsOrNil forCPPInstance:aCPlusPlusObjectOrNil
  1531 	    ^ self tryAgainWithAsyncSafeArguments:argumentsOrNil forCPPInstance:aCPlusPlusObjectOrNil
  1532         ].
  1532 	].
  1533 
  1533 
  1534         self primitiveFailed.   "see failureCode and failureInfo for details"
  1534 	self primitiveFailed.   "see failureCode and failureInfo for details"
  1535         ^ nil
  1535 	^ nil
  1536     ].
  1536     ].
  1537 
  1537 
  1538     returnType isSymbol ifTrue:[
  1538     returnType isSymbol ifTrue:[
  1539         returnValueClass notNil ifTrue:[
  1539 	returnValueClass notNil ifTrue:[
  1540             self isConstReturnValue ifTrue:[
  1540 	    self isConstReturnValue ifTrue:[
  1541                 returnValue changeClassTo:returnValueClass.
  1541 		returnValue changeClassTo:returnValueClass.
  1542                 ^ returnValue
  1542 		^ returnValue
  1543             ].
  1543 	    ].
  1544             ^ returnValueClass fromExternalAddress:returnValue.
  1544 	    ^ returnValueClass fromExternalAddress:returnValue.
  1545         ].
  1545 	].
  1546     ] ifFalse:[
  1546     ] ifFalse:[
  1547         returnType isCPointer ifTrue:[
  1547 	returnType isCPointer ifTrue:[
  1548             returnType baseType isCStruct ifTrue:[
  1548 	    returnType baseType isCStruct ifTrue:[
  1549                 stClass := Smalltalk classNamed:returnType baseType name.
  1549 		stClass := Smalltalk classNamed:returnType baseType name.
  1550                 stClass notNil ifTrue:[
  1550 		stClass notNil ifTrue:[
  1551                     self isConstReturnValue ifTrue:[
  1551 		    self isConstReturnValue ifTrue:[
  1552                         returnValue changeClassTo:returnValueClass.
  1552 			returnValue changeClassTo:returnValueClass.
  1553                         ^ returnValue
  1553 			^ returnValue
  1554                     ].
  1554 		    ].
  1555                     ^ stClass fromExternalAddress:returnValue.
  1555 		    ^ stClass fromExternalAddress:returnValue.
  1556                 ].
  1556 		].
  1557             ].
  1557 	    ].
  1558             returnType baseType isCChar ifTrue:[
  1558 	    returnType baseType isCChar ifTrue:[
  1559                 ^ returnValue stringAt:1
  1559 		^ returnValue stringAt:1
  1560             ].
  1560 	    ].
  1561         ].
  1561 	].
  1562     ].
  1562     ].
  1563 
  1563 
  1564     ^ returnValue
  1564     ^ returnValue
  1565 
  1565 
  1566     "Created: / 01-08-2006 / 13:56:23 / cg"
  1566     "Created: / 01-08-2006 / 13:56:23 / cg"
  1573      then try the call again, copy changed values back, and release the memeory."
  1573      then try the call again, copy changed values back, and release the memeory."
  1574 
  1574 
  1575     |saveArguments anyBadArg result originalToSaveArgMapping|
  1575     |saveArguments anyBadArg result originalToSaveArgMapping|
  1576 
  1576 
  1577     argumentsOrNil isNil ifTrue:[
  1577     argumentsOrNil isNil ifTrue:[
  1578         ^ self primitiveFailed
  1578 	^ self primitiveFailed
  1579     ].
  1579     ].
  1580     thisContext isRecursive ifTrue: [^self primitiveFailed].
  1580     thisContext isRecursive ifTrue: [^self primitiveFailed].
  1581 
  1581 
  1582     anyBadArg := false.
  1582     anyBadArg := false.
  1583     originalToSaveArgMapping := IdentityDictionary new.
  1583     originalToSaveArgMapping := IdentityDictionary new.
  1584 
  1584 
  1585     saveArguments := argumentsOrNil 
  1585     saveArguments := argumentsOrNil
  1586                         collect:[:eachArg |
  1586 			collect:[:eachArg |
  1587                             |saveArg|
  1587 			    |saveArg|
  1588 
  1588 
  1589                             (originalToSaveArgMapping includesKey:eachArg) ifTrue:[
  1589 			    (originalToSaveArgMapping includesKey:eachArg) ifTrue:[
  1590                                 saveArg := originalToSaveArgMapping at:eachArg
  1590 				saveArg := originalToSaveArgMapping at:eachArg
  1591                             ] ifFalse:[
  1591 			    ] ifFalse:[
  1592                                 eachArg isString ifTrue:[
  1592 				eachArg isString ifTrue:[
  1593                                     saveArg := (ExternalBytes fromString:eachArg) register.
  1593 				    saveArg := (ExternalBytes fromString:eachArg) register.
  1594                                     anyBadArg := true.
  1594 				    anyBadArg := true.
  1595                                     originalToSaveArgMapping at:eachArg put:saveArg.
  1595 				    originalToSaveArgMapping at:eachArg put:saveArg.
  1596                                 ] ifFalse:[
  1596 				] ifFalse:[
  1597                                     eachArg isByteCollection ifTrue:[
  1597 				    eachArg isByteCollection ifTrue:[
  1598                                         saveArg := (ExternalBytes from:eachArg) register.
  1598 					saveArg := (ExternalBytes from:eachArg) register.
  1599                                         originalToSaveArgMapping at:eachArg put:saveArg.
  1599 					originalToSaveArgMapping at:eachArg put:saveArg.
  1600                                         anyBadArg := true.
  1600 					anyBadArg := true.
  1601                                     ] ifFalse:[
  1601 				    ] ifFalse:[
  1602                                         saveArg := eachArg
  1602 					saveArg := eachArg
  1603                                     ]
  1603 				    ]
  1604                                 ].
  1604 				].
  1605                             ].
  1605 			    ].
  1606                             saveArg
  1606 			    saveArg
  1607                         ].
  1607 			].
  1608 
  1608 
  1609     anyBadArg ifFalse:[
  1609     anyBadArg ifFalse:[
  1610         "avoid recursion..."
  1610 	"avoid recursion..."
  1611         ^ self primitiveFailed
  1611 	^ self primitiveFailed
  1612     ].
  1612     ].
  1613 
  1613 
  1614     result := self invokeFFIwithArguments:saveArguments forCPPInstance:aCPlusPlusObjectOrNil.
  1614     result := self invokeFFIwithArguments:saveArguments forCPPInstance:aCPlusPlusObjectOrNil.
  1615 
  1615 
  1616     "/ copy back !!
  1616     "/ copy back !!
  1617     originalToSaveArgMapping keysAndValuesDo:[:arg :saveArg |
  1617     originalToSaveArgMapping keysAndValuesDo:[:arg :saveArg |
  1618         arg isSymbol ifFalse:[
  1618 	arg isSymbol ifFalse:[
  1619             arg replaceFrom:1 to:(arg size) with:saveArg startingAt:1.
  1619 	    arg replaceFrom:1 to:(arg size) with:saveArg startingAt:1.
  1620         ].
  1620 	].
  1621         saveArg free.
  1621 	saveArg free.
  1622     ].
  1622     ].
  1623     ^ result.
  1623     ^ result.
  1624 
  1624 
  1625     "Modified (format): / 06-11-2012 / 10:52:41 / anwild"
  1625     "Modified (format): / 06-11-2012 / 10:52:41 / anwild"
  1626 ! !
  1626 ! !
  1637 ! !
  1637 ! !
  1638 
  1638 
  1639 !ExternalLibraryFunction class methodsFor:'documentation'!
  1639 !ExternalLibraryFunction class methodsFor:'documentation'!
  1640 
  1640 
  1641 version_CVS
  1641 version_CVS
  1642     ^ '$Header: /cvs/stx/stx/libbasic/ExternalLibraryFunction.st,v 1.90 2012-11-16 09:27:00 stefan Exp $'
  1642     ^ '$Header: /cvs/stx/stx/libbasic/ExternalLibraryFunction.st,v 1.91 2013-01-02 12:45:06 cg Exp $'
  1643 !
  1643 !
  1644 
  1644 
  1645 version_SVN
  1645 version_SVN
  1646     ^ '§ Id: ExternalLibraryFunction.st 10643 2011-06-08 21:53:07Z vranyj1  §'
  1646     ^ '§ Id: ExternalLibraryFunction.st 10643 2011-06-08 21:53:07Z vranyj1  §'
  1647 ! !
  1647 ! !