[squeak-dev] FFI: FFI-Tests-mt.22.mcz

commits at source.squeak.org commits at source.squeak.org
Mon May 3 14:54:42 UTC 2021


Marcel Taeumel uploaded a new version of FFI-Tests to project FFI:
http://source.squeak.org/FFI/FFI-Tests-mt.22.mcz

==================== Summary ====================

Name: FFI-Tests-mt.22
Author: mt
Time: 3 May 2021, 4:54:41.730479 pm
UUID: a156622d-6212-3c45-9f7a-7c8017118210
Ancestors: FFI-Tests-mt.21

Big refactoring of FFI tests:

- Adds message categories for FFITestLibrary
- Replicates all tests in FFIPluginTests to also test invocation through library and construction as ExternalLibraryFunction. See FFIPluginConstrutedTests and FFIPluginLibraryTests.
- Extracts tests about structures (and unions etc.) that do not need the test-plugin to ExternalStructureTests
- In field definitions, replace all uses of "short/long/longlong" with "int16_t/int32_t/int64_t" for improved readability
- Fixes the definitions that actually rely on c_long because they use "long" in the "sqFFITestFuncs.c"
- Compiles instance-side methods in FFITestLibrary as needed, see FFIPluginLibraryTests >> #invoke:withArguments:.

Note that, for simplicity, the new design of the FFIPluginTests hierarchy requires the class-side methods in FFITestLibrary to match the C function names. Arguments can be attached with "with:". See all implementors of  #invoke:withArguments: to learn more.

If you want to improve readability over those C names, use either method comments or the actual test selector. See #testUnsignedIntegerRange as an example.

=============== Diff against FFI-Tests-mt.21 ===============

Item was added:
+ TestCase subclass: #ExternalStructureTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'FFI-Tests'!

Item was added:
+ ----- Method: ExternalStructureTests>>test01AccessingUnion (in category 'tests') -----
+ test01AccessingUnion
+ 
+ 	| ufi |
+ 	ufi := FFITestUfi new.
+ 	ufi i1: 2.
+ 	self assert: 2 equals: ufi i1.
+ 	ufi f1: 1.0.
+ 	self assert: 1.0 equals: ufi f1.
+ 	self assert: 1.0 asIEEE32BitWord equals: ufi i1.
+ 	ufi i1: 2.0 asIEEE32BitWord.
+ 	self assert: 2.0 equals: ufi f1.!

Item was added:
+ ----- Method: ExternalStructureTests>>test02AccessingStructure (in category 'tests') -----
+ test02AccessingStructure
+ 
+ 	| pt |
+ 	pt := FFITestPoint2 new.
+ 	pt x: 10; y: 20.
+ 	self assert: 10 equals: pt x.
+ 	self assert: 20 equals: pt y.!

Item was added:
+ ----- Method: ExternalStructureTests>>test03AccessingExternalData (in category 'tests') -----
+ test03AccessingExternalData
+ 
+ 	| somePoints firstPoint |
+ 	somePoints := FFITestPoint2 allocate: 5.
+ 	self assert: 5 equals: somePoints size.
+ 	firstPoint := somePoints at: 1.
+ 	self assert: 0 at 0 equals: firstPoint asPoint.
+ 	firstPoint setX: 2 setY: 3.
+ 	self assert: 2 at 3 equals: firstPoint asPoint.!

Item was added:
+ ----- Method: ExternalTypeTests>>testAtomicTypeNameByType (in category 'tests') -----
+ testAtomicTypeNameByType
+ 
+ 	AtomicTypeNames do: [:symbol | | typeName |
+ 		typeName := symbol.
+ 		self
+ 			assert: typeName
+ 			equals: (ExternalType typeNamed: typeName) typeName;
+ 			assert: typeName
+ 			equals: (AtomicTypes at: typeName) typeName.
+ 		typeName := (AtomicTypes at: symbol) asPointerType typeName.
+ 		self
+ 			assert: typeName
+ 			equals: (ExternalType typeNamed: typeName) typeName].!

Item was added:
+ FFIPluginTests subclass: #FFIPluginConstructedTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'FFI-Tests'!

Item was added:
+ ----- Method: FFIPluginConstructedTests class>>shouldInheritSelectors (in category 'testing') -----
+ shouldInheritSelectors
+ 	^ true!

Item was added:
+ ----- Method: FFIPluginConstructedTests>>expectedFailures (in category 'failures') -----
+ expectedFailures
+ 	"We can actually call that one function with 20 arguments. :-)"
+ 	
+ 	^ super expectedFailures copyWithout: #testMixedDoublesAndLongsSum!

Item was added:
+ ----- Method: FFIPluginConstructedTests>>invoke:withArguments: (in category 'support') -----
+ invoke: functionName withArguments: someObjects
+ 	"Use primitive 117 to invoke the call, not 120."
+ 	
+ 	| prototype externalFunction |
+ 	prototype := (FFITestLibrary class >> (self lookupSelector: functionName numArgs: someObjects size)) externalLibraryFunction.
+ 	externalFunction := ExternalLibraryFunction
+ 		name: functionName module: prototype module
+ 		callType: prototype flags returnType: prototype argTypes first
+ 		argumentTypes: prototype argTypes allButFirst.
+ 	^ externalFunction invokeWithArguments: someObjects!

Item was added:
+ FFIPluginTests subclass: #FFIPluginLibraryTests
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'FFI-Tests'!

Item was added:
+ ----- Method: FFIPluginLibraryTests class>>shouldInheritSelectors (in category 'testing') -----
+ shouldInheritSelectors
+ 	^ true!

Item was added:
+ ----- Method: FFIPluginLibraryTests>>invoke:withArguments: (in category 'support') -----
+ invoke: functionName withArguments: someObjects
+ 	"Use an instance of the library. Compile class-side methods to instance-side methods as needed."
+ 
+ 	| selector library |
+ 	selector := self lookupSelector: functionName numArgs: someObjects size.
+ 	library := FFITestLibrary new.
+ 
+ 	(library respondsTo: selector) ifFalse: [ | signature source prototype |
+ 		"1) Build method signature."
+ 		signature := String streamContents: [:s | | index |
+ 			index := 0. selector do: [:char | s nextPut: char.
+ 				char = $: ifTrue: [ index := index + 1.
+ 					s space; nextPutAll: 'arg'; nextPutAll: index asString; space]]].
+ 		"2) Construct method source."
+ 		prototype := library class class compiledMethodAt: selector.
+ 		source := '{1}\	{2}\	<generated>\	{3}\	^ self externalCallFailed' withCRs
+ 			format: {
+ 				signature.
+ 				'"This method was automatically generated. See {1}>>{2}"'
+ 					format: {prototype methodClass. prototype selector}.
+ 				 prototype externalLibraryFunction copy
+ 					setModule: nil; printString }.
+ 		"3) Compile instance-side FFI call in library."
+ 		library class compile: source classified: '*autogenerated - primitives'].
+ 
+ 	^ library perform: selector withArguments: someObjects!

Item was changed:
  TestCase subclass: #FFIPluginTests
+ 	instanceVariableNames: 'heapObject'
- 	instanceVariableNames: ''
  	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'FFI-Tests'!
  
  !FFIPluginTests commentStamp: '<historical>' prior: 0!
  SUnitized tests for the FFI (mostly the plugin side)!

Item was added:
+ ----- Method: FFIPluginTests>>expectedFailures (in category 'failures') -----
+ expectedFailures
+ 
+ 	^ #(
+ 		testIntAliasCallReturnIntAlias "return-type coercing failed"
+ 		testIntCallReturnIntAlias "return-type coercing failed"
+ 		testMixedDoublesAndLongsSum "more than 15 method args needed"
+ 		testSumStructSslf4 "some overflow issue, maybe expected")!

Item was added:
+ ----- Method: FFIPluginTests>>invoke: (in category 'support') -----
+ invoke: selector
+ 
+ 	^ self invoke: selector withArguments: #()!

Item was added:
+ ----- Method: FFIPluginTests>>invoke:with: (in category 'support') -----
+ invoke: selector with: arg1
+ 
+ 	^ self invoke: selector withArguments: {arg1}!

Item was added:
+ ----- Method: FFIPluginTests>>invoke:with:with: (in category 'support') -----
+ invoke: selector with: arg1 with: arg2
+ 
+ 	^ self invoke: selector withArguments: {arg1. arg2}!

Item was added:
+ ----- Method: FFIPluginTests>>invoke:with:with:with: (in category 'support') -----
+ invoke: selector with: arg1 with: arg2 with: arg3
+ 
+ 	^ self invoke: selector withArguments: {arg1. arg2. arg3}!

Item was added:
+ ----- Method: FFIPluginTests>>invoke:with:with:with:with: (in category 'support') -----
+ invoke: selector with: arg1 with: arg2 with: arg3 with: arg4
+ 
+ 	^ self invoke: selector withArguments: {arg1. arg2. arg3. arg4}!

Item was added:
+ ----- Method: FFIPluginTests>>invoke:with:with:with:with:with: (in category 'support') -----
+ invoke: selector with: arg1 with: arg2 with: arg3 with: arg4 with: arg5
+ 
+ 	^ self invoke: selector withArguments: {arg1. arg2. arg3. arg4. arg5}!

Item was added:
+ ----- Method: FFIPluginTests>>invoke:withArguments: (in category 'support') -----
+ invoke: functionName withArguments: someObjects
+  
+ 	^ FFITestLibrary
+ 		perform: (self lookupSelector: functionName numArgs: someObjects size)
+ 		withArguments: someObjects!

Item was added:
+ ----- Method: FFIPluginTests>>lookupSelector:numArgs: (in category 'support') -----
+ lookupSelector: functionName numArgs: numArgs
+ 
+ 	^ Symbol lookup: (
+ 		numArgs > 0
+ 			ifFalse: [functionName]
+ 			ifTrue: [
+ 				functionName, ':'
+ 					, (Array new: (numArgs min: 15) - 1 withAll: 'with:') join])!

Item was added:
+ ----- Method: FFIPluginTests>>tearDown (in category 'running') -----
+ tearDown
+ 
+ 	heapObject ifNotNil: [heapObject free].!

Item was added:
+ ----- Method: FFIPluginTests>>test4IntSum (in category 'tests - atomics') -----
+ test4IntSum
+ 
+ 	| result n interval |
+ 	n := 4.
+ 	interval := 1 - n * n to: n * n by: 2 * n + 1.
+ 	result := self invoke: 'ffiTest4IntSum' withArguments: interval asArray.
+ 	self assert: interval sum equals: result!

Item was changed:
+ ----- Method: FFIPluginTests>>test8IntSum (in category 'tests - atomics') -----
- ----- Method: FFIPluginTests>>test8IntSum (in category 'tests') -----
  test8IntSum
+ 
+ 	| result n interval |
+ 	n := 8.
- 	"Test using generic FFI spec"
- 	| result meth n interval |
- 	meth := ExternalLibraryFunction
- 				name:'ffiTest8IntSum' module: FFITestLibrary moduleName
- 				callType: 0 returnType: ExternalType long
- 				argumentTypes: (Array new: (n := 8) withAll: ExternalType long).
  	interval := 1 - n * n to: n * n by: 2 * n + 1.
+ 	result := self invoke: 'ffiTest8IntSum' withArguments: interval asArray.
- 	result := meth invokeWithArguments: interval asArray.
  	self assert: interval sum equals: result!

Item was changed:
+ ----- Method: FFIPluginTests>>test8LongLongSum (in category 'tests - atomics') -----
- ----- Method: FFIPluginTests>>test8LongLongSum (in category 'tests') -----
  test8LongLongSum
+ 
+ 	| result n interval |
+ 	n := 8.
- 	"Test using generic FFI spec"
- 	| result meth n interval |
- 	meth := ExternalLibraryFunction
- 				name:'ffiTest8LongLongSum' module: FFITestLibrary moduleName
- 				callType: 0 returnType: ExternalType signedLongLong
- 				argumentTypes: (Array new: (n := 8) withAll: ExternalType signedLongLong).
  	interval := 1 - n * n << 32 + (1 - n * n) to: n * n - n << 32 + (3 * n * n) by: 2 * n << 32 + (3 * n).
+ 	result := self invoke: 'ffiTest8LongLongSum' withArguments: interval asArray.
- 	result := meth invokeWithArguments: interval asArray.
  	self assert: interval sum equals: result!

Item was added:
+ ----- Method: FFIPluginTests>>test8LongSum (in category 'tests - atomics') -----
+ test8LongSum
+ 
+ 	| result n interval |
+ 	n := 8.
+ 	interval := 1 - n * n to: n * n by: 2 * n + 1.
+ 	result := self invoke: 'ffiTest8longSum' withArguments: interval asArray.
+ 	self assert: interval sum equals: result!

Item was removed:
- ----- Method: FFIPluginTests>>testAccessingUnion (in category 'tests - union') -----
- testAccessingUnion
- 	| ufi |
- 	ufi := FFITestUfi new.
- 	ufi i1: 2.
- 	self assert: 2 equals: ufi i1.
- 	ufi f1: 1.0.
- 	self assert: 1.0 equals: ufi f1.
- 	self assert: 1.0 asIEEE32BitWord equals: ufi i1.
- 	ufi i1: 2.0 asIEEE32BitWord.
- 	self assert: 2.0 equals: ufi f1.!

Item was added:
+ ----- Method: FFIPluginTests>>testBoolsToInts (in category 'tests - other') -----
+ testBoolsToInts
+ 
+ 	| result |
+ 	result := FFITestLibrary ffiTestBool: true with: false with: true with: false.
+ 	self assert: result.
+ 	result := FFITestLibrary ffiTestBool: -1 with: 1 with: 0 with: 0.
+ 	self deny: result.
+ 	result := FFITestLibrary ffiTestBool: false with: false with: true with: true.
+ 	self deny: result.!

Item was added:
+ ----- Method: FFIPluginTests>>testChars (in category 'tests - atomics') -----
+ testChars
+ 
+ 	| result |
+ 	result := self invoke: 'ffiTestChars' with: $A with: 65 with: 65.0 with: true.
+ 	self assert: result isCharacter.
+ 	self assert: result asciiValue = 130.!

Item was removed:
- ----- Method: FFIPluginTests>>testConstructedCharCall (in category 'tests') -----
- testConstructedCharCall
- 	"Test using generic FFI spec"
- 	| result meth |
- 	meth := ExternalLibraryFunction
- 		name:'ffiTestChars' module: FFITestLibrary moduleName 
- 		callType: ExternalFunction callTypeCDecl returnType: ExternalType char
- 		argumentTypes: (Array new: 4 withAll: ExternalType char).
- 	result := meth invokeWith: $A with: 65 with: 65.0 with: true.
- 	self assert: result isCharacter.
- 	self assert: 130 equals: result asciiValue!

Item was removed:
- ----- Method: FFIPluginTests>>testConstructedDoubleCall (in category 'tests') -----
- testConstructedDoubleCall
- 	"Test using generic FFI spec"
- 	| result meth |
- 	meth := ExternalLibraryFunction
- 		name:'ffiTestDoubles' module: FFITestLibrary moduleName 
- 		callType: ExternalFunction callTypeCDecl returnType: ExternalType double
- 		argumentTypes: (Array new: 2 withAll: ExternalType double).
- 	result := meth invokeWithArguments: (Array with: 41 with: true).
- 	self assert: 42.0 equals: result!

Item was removed:
- ----- Method: FFIPluginTests>>testConstructedFloatCall (in category 'tests') -----
- testConstructedFloatCall
- 	"Test using generic FFI spec"
- 	| result meth |
- 	meth := ExternalLibraryFunction
- 		name:'ffiTestFloats' module: FFITestLibrary moduleName 
- 		callType: ExternalFunction callTypeCDecl returnType: ExternalType float
- 		argumentTypes: (Array new: 2 withAll: ExternalType float).
- 	result := meth invokeWith: $A with: 65.0.
- 	self assert: 130.0 equals: result!

Item was removed:
- ----- Method: FFIPluginTests>>testConstructedIntCall (in category 'tests') -----
- testConstructedIntCall
- 	"Test using generic FFI spec"
- 	| result meth |
- 	meth := ExternalLibraryFunction
- 		name:'ffiTestInts' module: FFITestLibrary moduleName
- 		callType: ExternalFunction callTypeCDecl returnType: ExternalType signedLong
- 		argumentTypes: (Array new: 4 withAll: ExternalType signedLong).
- 	result := meth invokeWith: $A with: 65 with: 65.0 with: true.
- 	self assert: 130 equals: result!

Item was removed:
- ----- Method: FFIPluginTests>>testConstructedPrintString (in category 'tests') -----
- testConstructedPrintString
- 	"Test using generic FFI spec"
- 	| result meth |
- 	meth := ExternalLibraryFunction
- 		name:'ffiPrintString' module: FFITestLibrary moduleName 
- 		callType: ExternalFunction callTypeCDecl returnType: ExternalType string
- 		argumentTypes: (Array with: ExternalType string).
- 	result := meth invokeWith:'Hello World!!'.
- 	self assert: 'Hello World!!' equals: result!

Item was removed:
- ----- Method: FFIPluginTests>>testConstructedShortCall (in category 'tests') -----
- testConstructedShortCall
- 	"Test using generic FFI spec"
- 	| result meth |
- 	meth := ExternalLibraryFunction
- 		name:'ffiTestShorts' module: FFITestLibrary moduleName 
- 		callType: ExternalFunction callTypeCDecl returnType: ExternalType short
- 		argumentTypes: (Array new: 4 withAll: ExternalType short).
- 	result := meth invokeWithArguments: (Array with: $A with: 65 with: 65.0 with: true).
- 	self assert: 130 equals: result!

Item was added:
+ ----- Method: FFIPluginTests>>testDoubles (in category 'tests - atomics') -----
+ testDoubles
+ 	
+ 	| result |
+ 	result := self invoke: 'ffiTestDoubles' with: $A with: 65.0.
+ 	self assert: 130.0 equals: result.
+ 	result := self invoke: 'ffiTestDoubles' with: 41 with: true.
+ 	self assert: 42.0 equals: result.!

Item was added:
+ ----- Method: FFIPluginTests>>testDoubles14 (in category 'tests - atomics') -----
+ testDoubles14
+ 
+ 	| result n args |
+ 	n := 14.
+ 	args := (123.456789 to: 3.210987 * 13 + 123.456789 by: 3.210987) asArray first: n.
+ 	result := self invoke: 'ffiTestDoubles14' withArguments: args.
+ 	self assert: args sum equals: result!

Item was added:
+ ----- Method: FFIPluginTests>>testDoubles9 (in category 'tests - atomics') -----
+ testDoubles9
+ 
+ 	| result |
+ 	result := self invoke: 'ffiTestDoubles9' withArguments: #(1.0 2.0 3.0 4.0 5.0 6.0 7.0 8.0 9.0).
+ 	self assert: 45.0 equals: result!

Item was added:
+ ----- Method: FFIPluginTests>>testFloats (in category 'tests - atomics') -----
+ testFloats
+ 
+ 	| result |
+ 	result :=self invoke: 'ffiTestFloats' with: $A with: 65.0.
+ 	self assert: 130.0 equals: result.!

Item was added:
+ ----- Method: FFIPluginTests>>testFloats13 (in category 'tests - atomics') -----
+ testFloats13
+ 
+ 	| result n args |
+ 	n := 13.
+ 	args := (123.456 to: 3.21 * 13 + 123.456 by: 3.21) asArray first: n.
+ 	result := self invoke: 'ffiTestFloats13' withArguments: args.
+ 	self assert: (result between: args sum - 0.0005 and: args sum + 0.0005)!

Item was removed:
- ----- Method: FFIPluginTests>>testFloats13Sum (in category 'tests') -----
- testFloats13Sum
- 	"Test using generic FFI spec"
- 	| result meth n args |
- 	meth := ExternalLibraryFunction
- 				name:'ffiTestFloats13' module: FFITestLibrary moduleName
- 				callType: 0 returnType: ExternalType float
- 				argumentTypes: (Array new: (n := 13) withAll: ExternalType float).
- 	args := (123.456 to: 3.21 * 13 + 123.456 by: 3.21) asArray first: 13.
- 	result := meth invokeWithArguments: args.
- 	self assert: (result between: args sum - 0.0005 and: args sum + 0.0005)!

Item was added:
+ ----- Method: FFIPluginTests>>testFloats14 (in category 'tests - atomics') -----
+ testFloats14
+ 
+ 	| result n args |
+ 	n := 14.
+ 	args := (123.456 to: 3.21 * 13 + 123.456 by: 3.21) asArray first: n.
+ 	result := self invoke: 'ffiTestFloats14' withArguments: args.
+ 	self assert: (result between: args sum - 0.0005 and: args sum + 0.0005)!

Item was added:
+ ----- Method: FFIPluginTests>>testFloats7 (in category 'tests - atomics') -----
+ testFloats7
+ 
+ 	| result n args |
+ 	n := 7.
+ 	args := (123.456 to: 3.21 * 13 + 123.456 by: 3.21) asArray first: n.
+ 	result := self invoke: 'ffiTestFloats7' withArguments: args.
+ 	self assert: (result between: args sum - 0.0005 and: args sum + 0.0005)!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericBoolCall (in category 'tests') -----
- testGenericBoolCall
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestBool: true with: false with: true with: false.
- 	self assert: result.!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericBoolCall2 (in category 'tests') -----
- testGenericBoolCall2
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestBool: false with: false with: true with: true.
- 	self deny: result.!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericBoolCall3 (in category 'tests') -----
- testGenericBoolCall3
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestBool: -1 with: 1 with: 0 with: 0.
- 	self deny: result.!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericCharCall (in category 'tests') -----
- testGenericCharCall
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestChar: $A with: 65 with: 65.0 with: true.
- 	self assert: result isCharacter.
- 	self assert: result asciiValue = 130.!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericDoubleCall (in category 'tests') -----
- testGenericDoubleCall
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestDoubles: $A with: 65.0.
- 	self assert: result = 130.0!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericDoubleCall2 (in category 'tests') -----
- testGenericDoubleCall2
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestDoubles9: 1.0 d: 2.0 d: 3.0 d: 4.0 d: 5.0 d: 6.0 d: 7.0 d: 8.0 d: 9.0.
- 	self assert: result = 45.0!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericFloatCall (in category 'tests') -----
- testGenericFloatCall
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestFloats: $A with: 65.0.
- 	self assert: result = 130.0!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericIntCall (in category 'tests') -----
- testGenericIntCall
- 	"Test using generic FFI spec"
- 	| result |
- 	self flag: #ffiLongVsInt.
- 	result := FFITestLibrary ffiTestInt: $A with: 65 with: 65.0 with: true.
- 	self assert: result = 130.!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericLongCall (in category 'tests') -----
- testGenericLongCall
- 	"Test using generic FFI spec"
- 	| result |
- 	self flag: #ffiLongVsInt.
- 	result := FFITestLibrary ffiTestLong: $A with: 65 with: 65.0 with: true.
- 	self assert: result = 130.!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericMixedDoublesIntAndStruct (in category 'tests') -----
- testGenericMixedDoublesIntAndStruct
- 	"Test using generic FFI spec"
- 	| result i struct |
- 	i := 42.
- 	struct := FFITestPoint4 new.
- 	struct x: 1. struct y: 2. struct z: 3. struct w: 4.
- 	result := FFITestLibrary ffiTestMixedDoublesIntAndStruct: 1.0 d: 2.0 d: 3.0 d: 4.0 d: 5.0 d: 6.0 d: 7.0 d: 8.0 d: 9.0 i: 42 s: struct.
- 	self assert: (result closeTo: 45.0 + 42 + 10) !

Item was removed:
- ----- Method: FFIPluginTests>>testGenericMixedFloatsAndDouble (in category 'tests') -----
- testGenericMixedFloatsAndDouble
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestMixedFloatsAndDouble: 1.2 with: 3.4 with: 5.6 with: 7.8.
- 	self assert: (result closeTo: 1.2 + 3.4 + 5.6 + 7.8) !

Item was removed:
- ----- Method: FFIPluginTests>>testGenericPrintString (in category 'tests') -----
- testGenericPrintString
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiPrintString:'Hello World!!'.
- 	self assert: result = 'Hello World!!'.!

Item was removed:
- ----- Method: FFIPluginTests>>testGenericShortCall (in category 'tests') -----
- testGenericShortCall
- 	"Test using generic FFI spec"
- 	| result |
- 	result := FFITestLibrary ffiTestShort: $A with: 65 with: 65.0 with: true.
- 	self assert: result = 130.!

Item was changed:
  ----- Method: FFIPluginTests>>testIntAliasCallReturnIntAlias (in category 'tests - type alias') -----
  testIntAliasCallReturnIntAlias
  
  	| result |
  	result := FFITestLibrary
+ 		ffiTestIntAlias4IntAliasSum: (FFITestIntAlias fromHandle: 1)
- 		ffiTestIntAlias4IntSum: (FFITestIntAlias fromHandle: 1)
  		with: (FFITestIntAlias fromHandle: 2)
  		with: (FFITestIntAlias fromHandle: 3)
  		with: (FFITestIntAlias fromHandle: 4).
  	self
  		assert: (result isKindOf: FFITestIntAlias);
  		assert: 10 equals: result value.!

Item was added:
+ ----- Method: FFIPluginTests>>testInts (in category 'tests - atomics') -----
+ testInts
+ 
+ 	| result |
+ 	result := self invoke: 'ffiTestInts' with: $A with: 65 with: 65.0 with: true.
+ 	self assert: 	$A asInteger + 65 equals: result.
+ !

Item was added:
+ ----- Method: FFIPluginTests>>testInts8 (in category 'tests - other') -----
+ testInts8
+ 
+ 	| result n interval |
+ 	n := 8.
+ 	interval := 1 - n * n to: n * n by: 2 * n + 1.
+ 	result := self invoke: 'ffiTestInts8' withArguments: interval asArray.
+ 	self assert: 42 equals: result!

Item was removed:
- ----- Method: FFIPluginTests>>testLibraryCharCall (in category 'tests - library') -----
- testLibraryCharCall
- 	"Test using call from ExternalLibrary"
- 	| result |
- 	result := FFITestLibrary new ffiTestChar: $A with: 65 with: 65.0 with: true.
- 	self assert: result isCharacter.
- 	self assert: result asciiValue = 130.!

Item was removed:
- ----- Method: FFIPluginTests>>testLibraryDoubleCall (in category 'tests - library') -----
- testLibraryDoubleCall
- 	"Test using call from ExternalLibrary"
- 	| result |
- 	result := FFITestLibrary new ffiTestDoubles: $A with: 65.0.
- 	self assert: result = 130.0!

Item was removed:
- ----- Method: FFIPluginTests>>testLibraryFloatCall (in category 'tests - library') -----
- testLibraryFloatCall
- 	"Test using call from ExternalLibrary"
- 	| result |
- 	result := FFITestLibrary new ffiTestFloats: $A with: 65.0.
- 	self assert: result = 130.0!

Item was removed:
- ----- Method: FFIPluginTests>>testLibraryIntCall (in category 'tests - library') -----
- testLibraryIntCall
- 	"Test using call from ExternalLibrary"
- 	| result |
- 	result := FFITestLibrary new ffiTestInt: $A with: 65 with: 65.0 with: true.
- 	self assert: result = 130.!

Item was removed:
- ----- Method: FFIPluginTests>>testLibraryPrintString (in category 'tests - library') -----
- testLibraryPrintString
- 	"Test using call from ExternalLibrary"
- 	| result |
- 	result := FFITestLibrary new ffiPrintString:'Hello World!!'.
- 	self assert: result = 'Hello World!!'.!

Item was added:
+ ----- Method: FFIPluginTests>>testLongLong (in category 'tests - atomics') -----
+ testLongLong
+ 	"Test passing and returning longlongs"
+ 	| long1 long2 long3 |
+ 	long1 := 16r123456789012.
+ 	long2 := (-1 << 31).
+ 	long3 := self invoke: 'ffiTestLongLong' with: long1 with: long2.
+ 	self assert: (long1 + long2) equals: long3.!

Item was added:
+ ----- Method: FFIPluginTests>>testLongLong8 (in category 'tests - atomics') -----
+ testLongLong8
+ 
+ 	| long1 long2 bytes result |
+ 	bytes := (1 to: 8) asArray.
+ 	long1 := 16r123456789012.
+ 	long2 := (-1 << 31).
+ 	result := self invoke: 'ffiTestLongLong8' withArguments: bytes, { long1 . long2 }.
+ 	self assert: (bytes sum + long1 + long2) equals: result.!

Item was added:
+ ----- Method: FFIPluginTests>>testLongLong8a1 (in category 'tests - atomics') -----
+ testLongLong8a1
+ 
+ 	| long1 long2 bytes result |
+ 	bytes := (1 to: 9) asArray.
+ 	long1 := 16r123456789012.
+ 	long2 := (-1 << 31).
+ 	result := self invoke: 'ffiTestLongLong8a1' withArguments: bytes, { long1 . long2 }.
+ 	self assert: (bytes sum + long1 + long2) equals: result.!

Item was added:
+ ----- Method: FFIPluginTests>>testLongLong8a2 (in category 'tests - atomics') -----
+ testLongLong8a2
+ 
+ 	| long1 long2 bytes result |
+ 	bytes := (1 to: 10) asArray.
+ 	long1 := 16r123456789012.
+ 	long2 := (-1 << 31).
+ 	result := self invoke: 'ffiTestLongLong8a2' withArguments: bytes, { long1 . long2 }.
+ 	self assert: (bytes sum + long1 + long2) equals: result.!

Item was changed:
+ ----- Method: FFIPluginTests>>testLongLongA1 (in category 'tests - atomics') -----
- ----- Method: FFIPluginTests>>testLongLongA1 (in category 'tests') -----
  testLongLongA1
  	"Test passing a char and two longlongs."
+ 	
+ 	| byte long1 long2 result |
- 	| byte long1 long2 long3 |
  	byte := 42.
  	long1 := 16r123456789012.
  	long2 := (-1 << 31).
+ 	result := self invoke: 'ffiTestLongLonga1' with: byte with: long1 with: long2.
+ 	self assert: (byte + long1 + long2) equals: result.!
- 	long3 := FFITestLibrary ffiTestLongLongA1: byte with: long1 with: long2.
- 	self assert: long3 = (byte + long1 + long2)!

Item was added:
+ ----- Method: FFIPluginTests>>testLongLongA2 (in category 'tests - atomics') -----
+ testLongLongA2
+ 
+ 	| byte1 byte2 long1 long2 result |
+ 	byte1 := 3.
+ 	byte2 := 4.
+ 	long1 := 16r123456789012.
+ 	long2 := (-1 << 31).
+ 	result := self invoke: 'ffiTestLongLonga2' with: byte1 with: byte2 with: long1 with: long2.
+ 	self assert: (byte1 + byte2 + long1 + long2) equals: result.!

Item was changed:
+ ----- Method: FFIPluginTests>>testLongLongA3 (in category 'tests - atomics') -----
- ----- Method: FFIPluginTests>>testLongLongA3 (in category 'tests') -----
  testLongLongA3
  	"Test passing a char, a longlong, and another char."
+ 	| byte1 long1 byte2 result |
- 	| byte1 long1 byte2 long2 |
  	byte1 := 3.
  	long1 := 16r123456789012.
  	byte2 := 4.
+ 	result := self invoke: 'ffiTestLongLonga3' with: byte1 with: long1 with: byte2.
+ 	self assert: (byte1 + long1 + byte2) equals: result.!
- 	long2 := FFITestLibrary ffiTestLongLongA3: byte1 with: long1 with: byte2.
- 	self assert: long2 = (byte1 + long1 + byte2)!

Item was removed:
- ----- Method: FFIPluginTests>>testLongLongs (in category 'tests') -----
- testLongLongs
- 	"Test passing and returning longlongs"
- 	| long1 long2 long3 |
- 	long1 := 16r123456789012.
- 	long2 := (-1 << 31).
- 	long3 := FFITestLibrary ffiTestLongLong: long1 with: long2.
- 	self assert: long3 = (long1 + long2)!

Item was added:
+ ----- Method: FFIPluginTests>>testLongLongs8 (in category 'tests - other') -----
+ testLongLongs8
+ 
+ 	| result n interval |
+ 	n := 8.
+ 	interval := 1 - n * n << 32 + (1 - n * n) to: n * n - n << 32 + (3 * n * n) by: 2 * n << 32 + (3 * n).
+ 	result := self invoke: 'ffiTestLongLongs8' withArguments: interval asArray.
+ 	self assert: 42 equals: result!

Item was changed:
+ ----- Method: FFIPluginTests>>testMixedDoublesAndLongsSum (in category 'tests - atomics') -----
- ----- Method: FFIPluginTests>>testMixedDoublesAndLongsSum (in category 'tests') -----
  testMixedDoublesAndLongsSum
+ 
+ 	| result n args |
+ 	n := 20.
- 	"Test using generic FFI spec"
- 	| result meth n args |
- 	meth := ExternalLibraryFunction
- 				name:'ffiTestMixedDoublesAndLongs' module: FFITestLibrary moduleName
- 				callType: 0 returnType: ExternalType double
- 				argumentTypes: ((1 to: (n := 20)) collect:[:i| i odd ifTrue: [ExternalType double] ifFalse: [ExternalType c_long]]).
  	args := (1 to: n) collect: [:i| i odd ifTrue: [(i // 2) odd ifTrue: [123.456 * (10 raisedTo: i)] ifFalse: [-654.321 * (10 raisedTo: i)]] ifFalse: [(i // 2) odd ifTrue: [54321 * i] ifFalse: [-54321 * i]]].
+ 	result := self invoke: 'ffiTestMixedDoublesAndLongs' withArguments: args asArray.
- 	result := meth invokeWithArguments: args asArray.
  	self assert: args sum equals: result!

Item was added:
+ ----- Method: FFIPluginTests>>testMixedDoublesIntAndStruct (in category 'tests - atomics') -----
+ testMixedDoublesIntAndStruct
+ 
+ 	| result i struct |
+ 	i := 42.
+ 	struct := FFITestPoint4 new.
+ 	struct x: 1. struct y: 2. struct z: 3. struct w: 4.
+ 	result := self
+ 		invoke: 'ffiTestMixedDoublesIntAndStruct'
+ 		withArguments: { 1.0 . 2.0 . 3.0 . 4.0 . 5.0 . 6.0 . 7.0 . 8.0 . 9.0 . 42 . struct }.
+ 	self assert: (result closeTo: 45.0 + 42 + 10).!

Item was added:
+ ----- Method: FFIPluginTests>>testMixedFloatsAndDouble (in category 'tests - atomics') -----
+ testMixedFloatsAndDouble
+ 
+ 	| result |
+ 	result := self invoke: 'ffiTestMixedFloatsAndDouble' with: 1.2 with: 3.4 with: 5.6 with: 7.8.
+ 	self assert: (result closeTo: 1.2 + 3.4 + 5.6 + 7.8) !

Item was changed:
  ----- Method: FFIPluginTests>>testMixedIntAndStruct (in category 'tests - structure') -----
  testMixedIntAndStruct
  	"Test passing an integer and two structures."
  	| i1 pt1 pt2 result |
  	i1 := 42.
  	pt1 := FFITestPoint2 new.
  	pt1 x: 3. pt1 y: 4.
  	pt2 := FFITestPoint2 new.
  	pt2 x: 5. pt2 y: 6.
+ 	result := self invoke: 'ffiTestMixedIntAndStruct' with: i1 with: pt1 with: pt2.
+ 	self assert: 60 equals: result.!
- 	result := FFITestLibrary ffiTestMixedIntAndStruct: i1 with: pt1 with: pt2.
- 	self assert: result = 60.!

Item was changed:
  ----- Method: FFIPluginTests>>testMixedIntAndStruct2 (in category 'tests - structure') -----
  testMixedIntAndStruct2
  	"Test passing an integer and two structures."
  	| i1 pt1 result |
  	i1 := 42.
  	pt1 := FFITestPoint4 new.
  	pt1 x: 3. pt1 y: 4. pt1 z: 5. pt1 w: 6.
+ 	result := self invoke: 'ffiTestMixedIntAndStruct2' with: i1 with: pt1.
+ 	self assert: 60 equals: result.!
- 	result := FFITestLibrary ffiTestMixedIntAndStruct2: i1 with: pt1.
- 	self assert: result = 60.!

Item was changed:
  ----- Method: FFIPluginTests>>testMixedIntAndStruct3 (in category 'tests - structure') -----
  testMixedIntAndStruct3
  	"Test passing an integer and a small structure."
  	| i1 pt1 result |
  	i1 := 42.
  	pt1 := FFISmallStruct1 new.
  	pt1 x: 3. pt1 y: 4.
+ 	result := self invoke: 'ffiTestMixedIntAndStruct3' with: i1 with: pt1.
+ 	self assert: 49 equals: result.!
- 	result := FFITestLibrary ffiTestMixedIntAndStruct3: i1 with: pt1.
- 	self assert: result = 49!

Item was changed:
  ----- Method: FFIPluginTests>>testPoint2 (in category 'tests - structure') -----
  testPoint2
  	"Test passing and returning up of structures >32bit and <= 64 bit"
  	| pt1 pt2 pt3 |
  	pt1 := FFITestPoint2 new.
  	pt1 x: 1. pt1 y: 2.
  	pt2 := FFITestPoint2 new.
  	pt2 x: 3. pt2 y: 4.
+ 	pt3 := self invoke: 'ffiTestStruct64' with: pt1 with: pt2.
- 	pt3 := FFITestLibrary ffiTestPoint2: pt1 with: pt2.
  	self assert: pt3 x = 4.
  	self assert: pt3 y = 6.!

Item was changed:
  ----- Method: FFIPluginTests>>testPoint4 (in category 'tests - structure') -----
  testPoint4
  	"Test passing and returning up of structures > 64 bit"
  	| pt1 pt2 pt3 |
  	pt1 := FFITestPoint4 new.
  	pt1 x: 1. pt1 y: 2. pt1 z: 3. pt1 w: 4.
  	pt2 := FFITestPoint4 new.
  	pt2 x: 5. pt2 y: 6. pt2 z: 7. pt2 w: 8.
+ 	pt3 := self invoke: 'ffiTestStructBig' with: pt1 with: pt2.
- 	pt3 := FFITestLibrary ffiTestPoint4: pt1 with: pt2.
  	self assert: pt3 x = 6.
  	self assert: pt3 y = 8.
  	self assert: pt3 z = 10.
  	self assert: pt3 w = 12.!

Item was added:
+ ----- Method: FFIPluginTests>>testPoint4Bigger (in category 'tests - structure') -----
+ testPoint4Bigger
+ 	"Test passing and returning up of structures > 64 bit"
+ 	| pt1 pt2 pt3 |
+ 	pt1 := FFITestPoint4 new.
+ 	pt1 x: 1. pt1 y: 2. pt1 z: 3. pt1 w: 4.
+ 	pt2 := FFITestPoint4 new.
+ 	pt2 x: 5. pt2 y: 6. pt2 z: 7. pt2 w: 8.
+ 	pt3 := self invoke: 'ffiTestStructBigger' with: pt1 with: pt2.
+ 	self assert: pt3 x equals: pt1 x.
+ 	self assert: pt3 y equals: pt1 y.
+ 	self assert: pt3 z equals: pt1 z.
+ 	self assert: pt3 w equals: pt1 w.
+ 	self assert: pt3 r equals: pt2 x.
+ 	self assert: pt3 s equals: pt2 y.
+ 	self assert: pt3 t equals: pt2 z.
+ 	self assert: pt3 u equals: pt2 w.
+ !

Item was changed:
  ----- Method: FFIPluginTests>>testPointers (in category 'tests - structure') -----
  testPointers
  	"Test passing and returning of pointers to structs"
  	| pt1 pt2 pt3 |
  	pt1 := FFITestPoint4 new.
  	pt1 x: 1. pt1 y: 2. pt1 z: 3. pt1 w: 4.
  	pt2 := FFITestPoint4 new.
  	pt2 x: 5. pt2 y: 6. pt2 z: 7. pt2 w: 8.
+ 	pt3 := heapObject := self invoke: 'ffiTestPointers' with: pt1 with: pt2.
- 	pt3 := FFITestLibrary ffiTestPointers: pt1 with: pt2.
  	self assert: pt3 x = 6.
  	self assert: pt3 y = 8.
  	self assert: pt3 z = 10.
  	self assert: pt3 w = 12.!

Item was added:
+ ----- Method: FFIPluginTests>>testPrintString (in category 'tests - other') -----
+ testPrintString
+ 
+ 	| result |
+ 	result := self invoke: 'ffiPrintString' with: 'Hello World!!'.
+ 	self assert: result = 'Hello World!!'.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructPassingUnionUfdUdSi2 (in category 'tests - union') -----
  testReturnStructPassingUnionUfdUdSi2
  	"Test returning struct made from 2 unions"
  	| ufd udSi2 sUfdUdSi2 |
+ 	ufd := self invoke: 'ffiTestInitUfd_d' with: Float pi.
+ 	udSi2 := self invoke: 'ffiTestInitUdSi2_ii' with: 1 with: 2.
+ 	sUfdUdSi2 := self invoke: 'ffiTestInitSUfdUdSi2' with: ufd with: udSi2.
- 	ufd := FFITestLibrary ffiTestInitUfdWithDouble: Float pi.
- 	udSi2 := FFITestLibrary ffiTestInitUdSi2WithInt: 1 int: 2.
- 	sUfdUdSi2 := FFITestLibrary ffiTestInitSUfd: ufd udSi2: udSi2.
  	self assert: Float pi equals: sUfdUdSi2 ufd1 d1.
  	self assert: 1 equals: sUfdUdSi2 udSii2 sii1 i1.
  	self assert: 2 equals: sUfdUdSi2 udSii2 sii1 i2.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructPassingUnionUfdUfi (in category 'tests - union') -----
  testReturnStructPassingUnionUfdUfi
  	"Test returning struct made from 2 unions"
  	| ufd ufi sUfdUfi |
+ 	ufd := self invoke: 'ffiTestInitUfd_d' with: Float pi.
+ 	ufi := self invoke: 'ffiTestInitUfi_i' with: 1.
+ 	sUfdUfi := self invoke: 'ffiTestInitSUfdUfi' with: ufd with: ufi.
- 	ufd := FFITestLibrary ffiTestInitUfdWithDouble: Float pi.
- 	ufi := FFITestLibrary ffiTestInitUfiWithInt: 1.
- 	sUfdUfi := FFITestLibrary ffiTestInitSUfd: ufd ufi: ufi.
  	self assert: Float pi equals: sUfdUfi ufd1 d1.
  	self assert: 1 equals: sUfdUfi ufi2 i1.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSSdi5 (in category 'tests - structure') -----
  testReturnStructSSdi5
  	"Test returning struct with five struct double int (64 + 32 bits)"
  	| ssdi5 |
+ 	ssdi5 := self invoke: 'ffiTestReturnSSdi5'.
- 	ssdi5 := FFITestLibrary ffiTestReturnSSdi5.
  	self assert: ssdi5 sdi1 d1 = 1.0.
  	self assert: ssdi5 sdi2 d1 = 2.0.
  	self assert: ssdi5 sdi3 d1 = 3.0.
  	self assert: ssdi5 sdi4 d1 = 4.0.
  	self assert: ssdi5 sdi5 d1 = 5.0.
  	self assert: ssdi5 sdi1 i2 = 1.
  	self assert: ssdi5 sdi2 i2 = 2.
  	self assert: ssdi5 sdi3 i2 = 3.
  	self assert: ssdi5 sdi4 i2 = 4.
  	self assert: ssdi5 sdi5 i2 = 5.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSd2 (in category 'tests - structure') -----
  testReturnStructSd2
  	"Test returning struct with two double"
  	| sd2 |
+ 	sd2 := self invoke: 'ffiTestReturnSd2'.
- 	sd2 := FFITestLibrary ffiTestReturnSd2.
  	self assert: sd2 d1 = 1.0.
  	self assert: sd2 d2 = 2.0.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSdi (in category 'tests - structure') -----
  testReturnStructSdi
  	"Test returning struct double int (64 + 32 bits)"
  	| sdi |
+ 	sdi := self invoke: 'ffiTestReturnSdi'.
- 	sdi := FFITestLibrary ffiTestReturnSdi.
  	self assert: sdi d1 = 1.0.
  	self assert: sdi i2 = 2.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSf2 (in category 'tests - structure') -----
  testReturnStructSf2
  	"Test returning struct with two float"
  	| sf2 |
+ 	sf2 := self invoke: 'ffiTestReturnSf2'.
- 	sf2 := FFITestLibrary ffiTestReturnSf2.
  	self assert: sf2 f1 = 1.0.
  	self assert: sf2 f2 = 2.0.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSf2d (in category 'tests - structure') -----
  testReturnStructSf2d
  	"Test returning struct with two float one double"
  	| sf2d |
+ 	sf2d := self invoke: 'ffiTestReturnSf2d'.
- 	sf2d := FFITestLibrary ffiTestReturnSf2d.
  	self assert: sf2d f1 = 1.0.
  	self assert: sf2d f2 = 2.0.
  	self assert: sf2d d3 = 3.0.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSf4 (in category 'tests - structure') -----
  testReturnStructSf4
  	"Test returning struct with four float"
  	| sf4 |
+ 	sf4 := self invoke: 'ffiTestReturnSf4'.
- 	sf4 := FFITestLibrary ffiTestReturnSf4.
  	self assert: sf4 f1 = 1.0.
  	self assert: sf4 f2 = 2.0.
  	self assert: sf4 f3 = 3.0.
  	self assert: sf4 f4 = 4.0.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSfdf (in category 'tests - structure') -----
  testReturnStructSfdf
  	"Test returning struct with float double float"
  	| sfdf |
+ 	sfdf := self invoke: 'ffiTestReturnSfdf'.
- 	sfdf := FFITestLibrary ffiTestReturnSfdf.
  	self assert: sfdf f1 = 1.0.
  	self assert: sfdf d2 = 2.0.
  	self assert: sfdf f3 = 3.0.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSfi (in category 'tests - structure') -----
  testReturnStructSfi
  	"Test returning struct with float int (32 + 32 bits)"
  	| sfi |
+ 	sfi := self invoke: 'ffiTestReturnSfi'.
- 	sfi := FFITestLibrary ffiTestReturnSfi.
  	self assert: sfi f1 = 1.0.
  	self assert: sfi i2 = 2.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSi2 (in category 'tests - structure') -----
  testReturnStructSi2
  	"Test returning struct with two int (32 bits)"
  	| si2 |
+ 	si2 := self invoke: 'ffiTestReturnSi2'.
- 	si2 := FFITestLibrary ffiTestReturnSi2.
  	self assert: si2 i1 = 1.
  	self assert: si2 i2 = 2.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSl2 (in category 'tests - structure') -----
  testReturnStructSl2
  	"Test returning struct with two long long int (64 bits)"
  	| sl2 |
+ 	sl2 := self invoke: 'ffiTestReturnSl2'.
- 	sl2 := FFITestLibrary ffiTestReturnSl2.
  	self assert: sl2 l1 = 1.
  	self assert: sl2 l2 = 2.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSs2 (in category 'tests - structure') -----
  testReturnStructSs2
  	"Test returning struct with two short int (16 bits)"
  	| ss2 |
+ 	ss2 := self invoke: 'ffiTestReturnSs2'.
- 	ss2 := FFITestLibrary ffiTestReturnSs2.
  	self assert: ss2 s1 = 1.
  	self assert: ss2 s2 = 2.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSs2i (in category 'tests - structure') -----
  testReturnStructSs2i
  	"Test returning struct with two short int (16 bits) one int (32 bits)"
  	| ss2i |
+ 	ss2i := self invoke: 'ffiTestReturnSs2i'.
- 	ss2i := FFITestLibrary ffiTestReturnSs2i.
  	self assert: ss2i s1 = 1.
  	self assert: ss2i s2 = 2.
  	self assert: ss2i i3 = 3.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSs4 (in category 'tests - structure') -----
  testReturnStructSs4
  	"Test returning struct with four short int (16 bits)"
  	| ss4 |
+ 	ss4 := self invoke: 'ffiTestReturnSs4'.
- 	ss4 := FFITestLibrary ffiTestReturnSs4.
  	self assert: ss4 s1 = 1.
  	self assert: ss4 s2 = 2.
  	self assert: ss4 s3 = 3.
  	self assert: ss4 s4 = 4.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSsSsf (in category 'tests - structure') -----
  testReturnStructSsSsf
  	"Test returning struct with short and sub structure short-float"
  	| ssSsf |
+ 	ssSsf := self invoke: 'ffiTestReturnSsSsf'.
- 	ssSsf := FFITestLibrary ffiTestReturnSsSsf.
  	self assert: ssSsf s1 = 1.
  	self assert: ssSsf ssf2 s1 = 2.
  	self assert: ssSsf ssf2 f2 = 3.0.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSsSsi (in category 'tests - structure') -----
  testReturnStructSsSsi
  	"Test returning struct with short and sub structure short-int"
  	| ssSsi |
+ 	ssSsi := self invoke: 'ffiTestReturnSsSsi'.
- 	ssSsi := FFITestLibrary ffiTestReturnSsSsi.
  	self assert: ssSsi s1 = 1.
  	self assert: ssSsi ssi2 s1 = 2.
  	self assert: ssSsi ssi2 i2 = 3.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSsf (in category 'tests - structure') -----
  testReturnStructSsf
  	"Test returning struct with short float (16 + 32 bits)"
  	| ssf |
+ 	ssf := self invoke: 'ffiTestReturnSsf'.
- 	ssf := FFITestLibrary ffiTestReturnSsf.
  	self assert: ssf s1 = 1.
  	self assert: ssf f2 = 2.0.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSsi (in category 'tests - structure') -----
  testReturnStructSsi
  	"Test returning struct with short int (16 + 32 bits)"
  	| ssi |
+ 	ssi := self invoke: 'ffiTestReturnSsi'.
- 	ssi := FFITestLibrary ffiTestReturnSsi.
  	self assert: ssi s1 = 1.
  	self assert: ssi i2 = 2.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSsis (in category 'tests - structure') -----
  testReturnStructSsis
  	"Test returning struct with short int short (16 + 32 + 16 bits)"
  	| ssis |
+ 	ssis := self invoke: 'ffiTestReturnSsis'.
- 	ssis := FFITestLibrary ffiTestReturnSsis.
  	self assert: ssis s1 = 1.
  	self assert: ssis i2 = 2.
  	self assert: ssis s3 = 3.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSslf (in category 'tests - structure') -----
  testReturnStructSslf
  	"Test returning struct with short longlong float (16 + 64 + 32 bits)"
  	| sslf |
+ 	sslf := self invoke: 'ffiTestReturnSslf'.
- 	sslf := FFITestLibrary ffiTestReturnSslf.
  	self assert: sslf s1 = 1.
  	self assert: sslf l2 = 2.
  	self assert: sslf f3 = 3.0.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnStructSsls (in category 'tests - structure') -----
  testReturnStructSsls
  	"Test returning struct with short longlong short (16 + 64 + 16 bits)"
  	| ssls |
+ 	ssls := self invoke: 'ffiTestReturnSsls'.
- 	ssls := FFITestLibrary ffiTestReturnSsls.
  	self assert: ssls s1 = 1.
  	self assert: ssls l2 = 2.
  	self assert: ssls s3 = 3.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnUnionUdSi2 (in category 'tests - union') -----
  testReturnUnionUdSi2
  	"Test returning union with double or 2 int (64 or 64 bits)"
  	| udSi2 |
+ 	udSi2 := self invoke: 'ffiTestInitUdSi2_d' with: Float pi.
- 	udSi2 := FFITestLibrary ffiTestInitUdSi2WithDouble: Float pi.
  	self assert: Float pi equals: udSi2 d1.
  	self assert: (Float pi basicAt: 1) equals: udSi2 sii1 i2. "Assume Little Endianness"
  	self assert: (Float pi basicAt: 2) equals: udSi2 sii1 i1.
+ 	udSi2 := self invoke: 'ffiTestInitUdSi2_ii' with: 1 with: 2.
- 	udSi2 := FFITestLibrary ffiTestInitUdSi2WithInt: 1 int: 2.
  	self assert: 1 equals: udSi2 sii1 i1.
  	self assert: 2 equals: udSi2 sii1 i2.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnUnionUfd (in category 'tests - union') -----
  testReturnUnionUfd
  	"Test returning union with float or double (32 or 64 bits)"
  	| ufd |
+ 	ufd := self invoke: 'ffiTestInitUfd_f' with: 1.0.
- 	ufd := FFITestLibrary ffiTestInitUfdWithFloat: 1.0.
  	self assert: 1.0 equals: ufd f1.
+ 	ufd := self invoke: 'ffiTestInitUfd_d' with: 2.0.
- 	ufd := FFITestLibrary ffiTestInitUfdWithDouble: 2.0.
  	self assert: 2 equals: ufd d1.!

Item was changed:
  ----- Method: FFIPluginTests>>testReturnUnionUfi (in category 'tests - union') -----
  testReturnUnionUfi
  	"Test returning union with float or int (32 or 32 bits)"
  	| ufi |
+ 	ufi := self invoke: 'ffiTestInitUfi_f' with: 1.0.
- 	ufi := FFITestLibrary ffiTestInitUfiWithFloat: 1.0.
  	self assert: 1.0 equals: ufi f1.
  	self assert: 1.0 asIEEE32BitWord equals: ufi i1.
+ 	ufi := self invoke: 'ffiTestInitUfi_i' with: 2.
- 	ufi := FFITestLibrary ffiTestInitUfiWithInt: 2.
  	self assert: 2 equals: ufi i1.!

Item was added:
+ ----- Method: FFIPluginTests>>testShorts (in category 'tests - atomics') -----
+ testShorts
+ 	
+ 	| result |
+ 	result := self invoke: 'ffiTestShorts' with: $A with: 65 with: 65.0 with: true.
+ 	self assert: 130 equals: result.!

Item was changed:
  ----- Method: FFIPluginTests>>testSmallStructureReturn (in category 'tests - structure') -----
  testSmallStructureReturn
  	"Test returning small structures (<4 bytes) which are returned in a register on some platforms."
  	| pt1 |
  
+ 	pt1 := self invoke: 'ffiTestSmallStructReturn'.
- 	pt1 := FFITestLibrary ffiTestSmallStructReturn.
  	self assert: pt1 x = 3.
  	self assert: pt1 y = 4.!

Item was changed:
  ----- Method: FFIPluginTests>>testSumStructSSdi5 (in category 'tests - structure') -----
  testSumStructSSdi5
  	"Test passing a structure larger than 8 eighbytes"
  	| sdi1 sdi2 sdi3 sdi4 sdi5 ssdi5 sum |
  	sdi1 := FFITestSdi new.
  	sdi1 d1: 0.5; i2: 16r12345678.
  	sdi2 := FFITestSdi new.
  	sdi2 d1: 0.25; i2: 16r01234567.
  	sdi3 := FFITestSdi new.
  	sdi3 d1: 0.125; i2: 3.
  	sdi4 := FFITestSdi new.
  	sdi4 d1: 2.0; i2: 1.
  	sdi5 := FFITestSdi new.
  	sdi5 d1: 4.0; i2: 2.
  	ssdi5 := FFITestSSdi5 new.
  	ssdi5 sdi1: sdi1; sdi2: sdi2; sdi3: sdi3; sdi4: sdi4; sdi5: sdi5.
+ 	sum := self invoke: 'ffiTestSumSSdi5' with: ssdi5.
- 	sum := FFITestLibrary ffiTestSumStructSdi5: ssdi5.
  	self assert: 0.5 + 16r12345678 + 0.25 + 16r01234567 + 0.125 + 3 + 2.0 + 1 + 4.0 + 2 equals: sum!

Item was added:
+ ----- Method: FFIPluginTests>>testSumStructSUfdUdsi2 (in category 'tests - structure') -----
+ testSumStructSUfdUdsi2
+ 	"Sum up the double parts of two unions in a struct. We have to malloc because we cannot (yet?) share parts of byte arrays between structures."
+ 	
+ 	| sUfdUdsi2 sum |
+ 	sUfdUdsi2 := heapObject := FFITestSUfdUdSi2 externalNew.
+ 	sUfdUdsi2 ufd1 d1: 123.456.
+ 	sUfdUdsi2 udSii2 d1: 456.123.
+ 	sum := self invoke: 'ffiTestSumSUfdUdSi2_d' with: sUfdUdsi2.
+ 	self assert: 123.456 + 456.123 equals: sum.!

Item was added:
+ ----- Method: FFIPluginTests>>testSumStructSUfdUfi (in category 'tests - structure') -----
+ testSumStructSUfdUfi
+ 	"Sum up the float parts of two unions in a struct. We have to malloc because we cannot (yet?) share parts of byte arrays between structures."
+ 
+ 	| sUfdUdsi2 result expected |
+ 	sUfdUdsi2 := heapObject := FFITestSUfdUfi externalNew.
+ 	sUfdUdsi2 ufd1 f1: 123.456.
+ 	sUfdUdsi2 ufi2 f1: 456.123.
+ 	result := self invoke: 'ffiTestSumSUfdUfi_f' with: sUfdUdsi2.
+ 	expected := 123.456 + 456.123.
+ 	self assert: (result between: expected - 0.0005 and: expected + 0.0005).!

Item was changed:
  ----- Method: FFIPluginTests>>testSumStructSdi (in category 'tests - structure') -----
  testSumStructSdi
  	"Test passing structure double int"
  	| sdi sum |
  	sdi := FFITestSdi new.
  	sdi d1: 0.5; i2: 16r12345678.
+ 	sum := self invoke: 'ffiTestSumSdi' with: sdi.
- 	sum := FFITestLibrary ffiTestSumSdi: sdi.
  	self assert: 0.5 + 16r12345678 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumStructSdi2 (in category 'tests - structure') -----
  testSumStructSdi2
  	"Test passing 2 structure double int"
  	| sdi1 sdi2 sum |
  	sdi1 := FFITestSdi new.
  	sdi1 d1: 0.5; i2: 16r12345678.
  	sdi2 := FFITestSdi new.
  	sdi2 d1: 0.25; i2: 16r01234567.
+ 	sum := self invoke: 'ffiTestSumSdi_2' with: sdi1 with: sdi2.
- 	sum := FFITestLibrary ffiTestSumSdi: sdi1 sdi: sdi2.
  	self assert: 0.5 + 16r12345678 + 0.25 + 16r01234567 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumStructSdi4 (in category 'tests - structure') -----
  testSumStructSdi4
  	"Test passing 4 structure double int"
  	| sdi1 sdi2 sdi3 sdi4 sum |
  	sdi1 := FFITestSdi new.
  	sdi1 d1: 0.5; i2: 16r12345678.
  	sdi2 := FFITestSdi new.
  	sdi2 d1: 0.25; i2: 16r01234567.
  	sdi3 := FFITestSdi new.
  	sdi3 d1: 0.125; i2: 3.
  	sdi4 := FFITestSdi new.
  	sdi4 d1: 2.0; i2: 1.
+ 	sum := self invoke: 'ffiTestSumSdi_4' with: sdi1 with: sdi2 with: sdi3 with: sdi4.
- 	sum := FFITestLibrary ffiTestSumSdi: sdi1 sdi: sdi2 sdi: sdi3 sdi: sdi4.
  	self assert: 0.5 + 16r12345678 + 0.25 + 16r01234567 + 0.125 + 3 + 2.0 + 1 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumStructSfd (in category 'tests - structure') -----
  testSumStructSfd
  	"Test passing structure float double"
  	| sfd sum |
  	sfd := FFITestSfd new.
  	sfd f1: 0.5; d2: 305419896.0.
+ 	sum := self invoke: 'ffiTestSumSfd' with: sfd.
- 	sum := FFITestLibrary ffiTestSumSfd: sfd.
  	self assert: 0.5 + 305419896.0 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumStructSfd2 (in category 'tests - structure') -----
  testSumStructSfd2
  	"Test passing 2 structure float double "
  	| sfd1 sfd2 sum |
  	sfd1 := FFITestSfd new.
  	sfd1 f1: 0.5; d2: 305419896.0.
  	sfd2 := FFITestSfd new.
  	sfd2 f1: 0.25; d2: 19088743.0.
+ 	sum := self invoke: 'ffiTestSumSfd_2' with: sfd1 with: sfd2.
- 	sum := FFITestLibrary ffiTestSumSfd: sfd1 sfd: sfd2.
  	self assert: 0.5 + 305419896.0 + 0.25 + 19088743.0 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumStructSfd4 (in category 'tests - structure') -----
  testSumStructSfd4
  	"Test passing 4 structure float double"
  	| sfd1 sfd2 sfd3 sfd4 sum |
  	sfd1 := FFITestSfd new.
  	sfd1 f1: 0.5; d2: 305419896.0.
  	sfd2 := FFITestSfd new.
  	sfd2 f1: 0.25; d2: 19088743.0.
  	sfd3 := FFITestSfd new.
  	sfd3 f1: 0.125; d2: 3.
  	sfd4 := FFITestSfd new.
  	sfd4 f1: 2.0; d2: 1.
+ 	sum := self invoke: 'ffiTestSumSfd_4' with: sfd1 with: sfd2 with: sfd3 with: sfd4.
- 	sum := FFITestLibrary ffiTestSumSfd: sfd1 sfd: sfd2 sfd: sfd3 sfd: sfd4.
  	self assert: 0.5 + 305419896.0 + 0.25 + 19088743.0 + 0.125 + 3.0 + 2.0 + 1.0 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumStructSslf (in category 'tests - structure') -----
  testSumStructSslf
  	"Test passing structure short long float"
  	| sslf sum |
  	sslf := FFITestSslf new.
  	sslf s1: -32768; l2: 16r1234560000; f3: 65536.0.
+ 	sum := self invoke: 'ffiTestSumSslf' with: sslf.
- 	sum := FFITestLibrary ffiTestSumSslf: sslf.
  	self assert: -32768 + 16r1234560000 + 65536.0 equals: sum!

Item was added:
+ ----- Method: FFIPluginTests>>testSumStructSslf2 (in category 'tests - structure') -----
+ testSumStructSslf2
+ 	"Test passing structure short long float"
+ 	| sslf1 sslf2 sum |
+ 	sslf1 := FFITestSslf new.
+ 	sslf1 s1: -32768; l2: 16r123456789012; f3: 65536.0.
+ 	sslf2 := FFITestSslf new.
+ 	sslf2 s1: 32767; l2: (-1 << 31); f3: -65536.0.	
+ 	sum := self invoke: 'ffiTestSumSslf_2' with: sslf1 with: sslf2.
+ 	self
+ 		assert: sslf1 s1 + sslf1 l2 + sslf1 f3 + sslf2 s1 + sslf2 l2 + sslf2 f3
+ 		equals: sum!

Item was added:
+ ----- Method: FFIPluginTests>>testSumStructSslf4 (in category 'tests - structure') -----
+ testSumStructSslf4
+ 	"Test passing structure short long float"
+ 	| sslf1 sslf2 sslf3 sslf4 sum |
+ 	sslf1 := FFITestSslf new.
+ 	sslf1 s1: -32768; l2: 16r123456789012; f3: 65536.0.
+ 	sslf2 := FFITestSslf new.
+ 	sslf2 s1: 32767; l2: (-1 << 31); f3: -65536.0.
+ 	sslf3 := FFITestSslf new.
+ 	sslf3 s1: 1; l2: 16r123456789012; f3: 123.456.	
+ 	sslf4 := FFITestSslf new.
+ 	sslf4 s1: 2; l2: (-1 << 31); f3: 456.123.	
+ 	sum := self invoke: 'ffiTestSumSslf_2' with: sslf1 with: sslf2.
+ 	self
+ 		assert: sslf1 s1 + sslf1 l2 + sslf1 f3 + sslf2 s1 + sslf2 l2 + sslf2 f3
+ 			+ sslf3 s1 + sslf3 l2 + sslf3 f3 + sslf4 s1 + sslf4 l2 + sslf4 f3
+ 		equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumdWithStructSdi4 (in category 'tests - structure') -----
  testSumdWithStructSdi4
  	"Test passing 4 structure double int"
  	| sdi1 sdi2 sdi3 sdi4 sum |
  	sdi1 := FFITestSdi new.
  	sdi1 d1: 0.5; i2: 16r12345678.
  	sdi2 := FFITestSdi new.
  	sdi2 d1: 0.25; i2: 16r01234567.
  	sdi3 := FFITestSdi new.
  	sdi3 d1: 0.125; i2: 3.
  	sdi4 := FFITestSdi new.
  	sdi4 d1: 2.0; i2: 1.
+ 	sum := self invoke: 'ffiTestSumdWithSdi_4' with: 5.0 with: sdi1 with: sdi2 with: sdi3 with: sdi4.
- 	sum := FFITestLibrary ffiTestSumd: 5.0 withSdi: sdi1 sdi: sdi2 sdi: sdi3 sdi: sdi4.
  	self assert: 5.0 + 0.5 + 16r12345678 + 0.25 + 16r01234567 + 0.125 + 3 + 2.0 + 1 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumdiWithStructSdi4 (in category 'tests - structure') -----
  testSumdiWithStructSdi4
  	"Test passing 4 structure double int"
  	| sdi1 sdi2 sdi3 sdi4 sum |
  	sdi1 := FFITestSdi new.
  	sdi1 d1: 0.5; i2: 16r12345678.
  	sdi2 := FFITestSdi new.
  	sdi2 d1: 0.25; i2: 16r01234567.
  	sdi3 := FFITestSdi new.
  	sdi3 d1: 0.125; i2: 3.
  	sdi4 := FFITestSdi new.
  	sdi4 d1: 2.0; i2: 1.
+ 	sum := self invoke: 'ffiTestSumdiWithSdi_4' withArguments: { 5.0 . 6 . sdi1 . sdi2 . sdi3 . sdi4 }.
- 	sum := FFITestLibrary ffiTestSumd: 5.0 i: 6 withSdi: sdi1 sdi: sdi2 sdi: sdi3 sdi: sdi4.
  	self assert: 5.0 + 6 + 0.5 + 16r12345678 + 0.25 + 16r01234567 + 0.125 + 3 + 2.0 + 1 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumfWithStructSfd4 (in category 'tests - structure') -----
  testSumfWithStructSfd4
  	"Test passing 4 structure float double"
  	| sfd1 sfd2 sfd3 sfd4 sum |
  	sfd1 := FFITestSfd new.
  	sfd1 f1: 0.5; d2: 305419896.0.
  	sfd2 := FFITestSfd new.
  	sfd2 f1: 0.25; d2: 19088743.0.
  	sfd3 := FFITestSfd new.
  	sfd3 f1: 0.125; d2: 3.
  	sfd4 := FFITestSfd new.
  	sfd4 f1: 2.0; d2: 1.
+ 	sum := self invoke: 'ffiTestSumfWithSfd_4' with: 5.0 with: sfd1 with: sfd2 with: sfd3 with: sfd4.
- 	sum := FFITestLibrary ffiTestSumf: 5.0 withSfd: sfd1 sfd: sfd2 sfd: sfd3 sfd: sfd4.
  	self assert: 5.0 + 0.5 + 305419896.0 + 0.25 + 19088743.0 + 0.125 + 3.0 + 2.0 + 1.0 equals: sum!

Item was changed:
  ----- Method: FFIPluginTests>>testSumiWithStructSdi4 (in category 'tests - structure') -----
  testSumiWithStructSdi4
  	"Test passing 4 structure double int"
  	| sdi1 sdi2 sdi3 sdi4 sum |
  	sdi1 := FFITestSdi new.
  	sdi1 d1: 0.5; i2: 16r12345678.
  	sdi2 := FFITestSdi new.
  	sdi2 d1: 0.25; i2: 16r01234567.
  	sdi3 := FFITestSdi new.
  	sdi3 d1: 0.125; i2: 3.
  	sdi4 := FFITestSdi new.
  	sdi4 d1: 2.0; i2: 1.
+ 	sum := self invoke: 'ffiTestSumiWithSdi_4' with: 5 with: sdi1 with: sdi2 with: sdi3 with: sdi4.
- 	sum := FFITestLibrary ffiTestSumi: 5 withSdi: sdi1 sdi: sdi2 sdi: sdi3 sdi: sdi4.
  	self assert: 5 + 0.5 + 16r12345678 + 0.25 + 16r01234567 + 0.125 + 3 + 2.0 + 1 equals: sum!

Item was removed:
- ----- Method: FFIPluginTests>>testUintRange (in category 'tests') -----
- testUintRange
- 	"Simple test for making sure the FFI can call certain numbers in the uint range."
- 	| result |
- 	self flag: #ffiLongVsInt.
- 	self shouldnt:[result := FFITestLibrary ffiTestUint:  3894967296 "1<<32-4e8 " with: 3894967296 with: 3103854339 with: 3103854339] raise: Error.
- 	self should: result =  -8e8.!

Item was removed:
- ----- Method: FFIPluginTests>>testUlongRange (in category 'tests') -----
- testUlongRange
- 	"Simple test for making sure the FFI can call certain numbers in the ulong range.
- 	Note: since primitive is using unsigned int under the hood, avoid an integer overflow by choosing appropriate unsigned values.
- 	Note: only first two parameters are added"
- 	| result |
- 	self flag: #ffiLongVsInt.
- 	self shouldnt:[result := FFITestLibrary ffiTestUlong:  3894967296 "1<<32-4e8 " with: 3894967296 with: 3103854339 with: 3103854339] raise: Error.
- 	self should: result =  -8e8.!

Item was added:
+ ----- Method: FFIPluginTests>>testUnsignedIntegerRange (in category 'tests - other') -----
+ testUnsignedIntegerRange
+ 	"Simple test for making sure the FFI can call certain numbers in the uint range. Note that only the first two parameters are summed up."
+ 
+ 	| result arg1 arg2 arg3 arg4 |
+ 	arg1 := arg2 := 3894967296 "1<<32-4e8".
+ 	arg3 := arg4 := 3103854339.
+ 	result := FFITestLibrary ffiTestUint: arg1 with: arg2 with: arg3 with: arg4.
+ 	self assert: -8e8 "due to overflow" equals: result.!

Item was changed:
  ----- Method: FFITestBiggerStruct class>>fields (in category 'field definition') -----
  fields
  	"FFITestBiggerStruct defineFields"
  	^#(
+ 		(x	'int64_t')
+ 		(y	'int64_t')
+ 		(z	'int64_t')
+ 		(w	'int64_t')
+ 		(r	'int64_t')
+ 		(s	'int64_t')
+ 		(t	'int64_t')
+ 		(u	'int64_t'))!
- 		(x	'longlong')
- 		(y	'longlong')
- 		(z	'longlong')
- 		(w	'longlong')
- 		(r	'longlong')
- 		(s	'longlong')
- 		(t	'longlong')
- 		(u	'longlong'))!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiPrintString: (in category 'other') -----
- ----- Method: FFITestLibrary class>>ffiPrintString: (in category 'primitives') -----
  ffiPrintString: aString
+ 	"
+ 	FFITestLibrary ffiPrintString: 'Hello'
+ 	"
- 	"FFITestLibrary ffiPrintString: 'Hello'"
  	<cdecl: char* 'ffiPrintString' (char *) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTest4IntAliasSum:with:with:with: (in category 'primitives - type alias') -----
- ffiTest4IntAliasSum: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary ffiTest4IntSum: 1 with: 2 with: 3 with: 4"
- 	<cdecl: int 'ffiTest4IntSum' (FFITestIntAlias FFITestIntAlias FFITestIntAlias FFITestIntAlias) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTest4IntSum:with:with:with: (in category 'atomic - int32_t') -----
- ----- Method: FFITestLibrary class>>ffiTest4IntSum:with:with:with: (in category 'primitives - long vs. int') -----
  ffiTest4IntSum: c1 with: c2 with: c3 with: c4
  	"FFITestLibrary ffiTest4IntSum: 1 with: 2 with: 3 with: 4"
+ 	<cdecl: int32_t 'ffiTest4IntSum' (int32_t int32_t int32_t int32_t) module:'SqueakFFIPrims'>
- 	<cdecl: int 'ffiTest4IntSum' (int int int int) module:'SqueakFFIPrims'>
- 	self flag: #ffiLongVsInt.
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTest4LongSum:with:with:with: (in category 'primitives - long vs. int') -----
- ffiTest4LongSum: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary ffiTest4LongSum: 1 with: 2 with: 3 with: 4"
- 	<cdecl: long 'ffiTest4IntSum' (long long long long) module:'SqueakFFIPrims'>
- 	self flag: #ffiLongVsInt.
- 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTest8IntSum:with:with:with:with:with:with:with: (in category 'atomic - int32_t') -----
- ----- Method: FFITestLibrary class>>ffiTest8IntSum:with:with:with:with:with:with:with: (in category 'primitives - long vs. int') -----
  ffiTest8IntSum: c1 with: c2 with: c3 with: c4 with: c5 with: c6 with: c7 with: c8
  	"FFITestLibrary ffiTest8IntSum: 1 with: 2 with: 3 with: 4 with: 5 with: 6 with: 7 with: 8"
+ 	<cdecl: int32_t 'ffiTest8IntSum' (int32_t int32_t int32_t int32_t int32_t int32_t int32_t int32_t) module:'SqueakFFIPrims'>
- 	<cdecl: int 'ffiTest8IntSum' (int int int int int int int int) module:'SqueakFFIPrims'>
- 	self flag: #ffiLongVsInt.
  	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTest8LongLongSum:with:with:with:with:with:with:with: (in category 'atomic - int64_t') -----
+ ffiTest8LongLongSum: long1 with: long2 with: long3 with: long4 with: long5 with: long6 with: long7 with: long8
+ 
+ 	<cdecl: longlong 'ffiTest8LongLongSum' (longlong longlong longlong longlong longlong longlong longlong longlong) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTest8LongSum:with:with:with:with:with:with:with: (in category 'primitives - long vs. int') -----
- ffiTest8LongSum: c1 with: c2 with: c3 with: c4 with: c5 with: c6 with: c7 with: c8
- 	"FFITestLibrary ffiTest8LongSum: 1 with: 2 with: 3 with: 4 with: 5 with: 6 with: 7 with: 8"
- 	<cdecl: long 'ffiTest8IntSum' (long long long long long long long long) module:'SqueakFFIPrims'>
- 	self flag: #ffiLongVsInt.
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTest8longSum:with:with:with:with:with:with:with: (in category 'atomic - c_long') -----
+ ffiTest8longSum: c1 with: c2 with: c3 with: c4 with: c5 with: c6 with: c7 with: c8
+ 	"FFITestLibrary ffiTest8LongSum: 1 with: 2 with: 3 with: 4 with: 5 with: 6 with: 7 with: 8"
+ 	<cdecl: c_long 'ffiTest8longSum' (c_long c_long c_long c_long c_long c_long c_long c_long) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestBool:with:with:with: (in category 'atomic - bool') -----
- ----- Method: FFITestLibrary class>>ffiTestBool:with:with:with: (in category 'primitives') -----
  ffiTestBool: b1 with: b2 with: b3 with: b4
  	"FFITestLibrary ffiTestBool: true with: false with: true with: false"
  	<cdecl: bool 'ffiTestInts' (bool bool bool bool) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestChar:with:with:with: (in category 'primitives') -----
- ffiTestChar: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary ffiTestChar: $A with: 65 with: 65.0 with: true"
- 	<cdecl: char 'ffiTestChars' (char char char char) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestChars:with:with:with: (in category 'atomic - char') -----
+ ffiTestChars: c1 with: c2 with: c3 with: c4
+ 	"Answers c1 + c2 as Character.
+ 	FFITestLibrary ffiTestChars: $A with: 32 with: 0 with: 0
+ 	"
+ 	<cdecl: char 'ffiTestChars' (char char char char) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestDoubles14:with:with:with:with:with:with:with:with:with:with:with:with:with: (in category 'atomic - floats') -----
+ ffiTestDoubles14: f1 with: f2 with: f3 with: f4 with: f5 with: f6 with: f7 with: f8 with: f9 with: f10 with: f11 with: f12 with: f13 with: f14
+ 
+ 	<cdecl: double 'ffiTestDoubles14' (double double double double double double double double double double double double double double) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestDoubles9:d:d:d:d:d:d:d:d: (in category 'primitives') -----
- ffiTestDoubles9: f1 d: f2 d: f3 d: f4 d: f5 d: f6 d: f7 d: f8 d: f9
- 	"FFITestLibrary ffiTestDoubles9: 1.0 d: 2.0 d: 3.0 d: 4.0 d: 5.0 d: 6.0 d: 7.0 d: 8.0 d: 9.0"
- 	<cdecl: double 'ffiTestDoubles9' (double double double double double double double double double) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestDoubles9:with:with:with:with:with:with:with:with: (in category 'atomic - floats') -----
+ ffiTestDoubles9: f1 with: f2 with: f3 with: f4 with: f5 with: f6 with: f7 with: f8 with: f9
+ 	"FFITestLibrary ffiTestDoubles9: 1.0 with: 2.0 with: 3.0 with: 4.0 with: 5.0 with: 6.0 with: 7.0 with: 8.0 with: 9.0"
+ 	<cdecl: double 'ffiTestDoubles9' (double double double double double double double double double) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestDoubles:with: (in category 'atomic - floats') -----
- ----- Method: FFITestLibrary class>>ffiTestDoubles:with: (in category 'primitives') -----
  ffiTestDoubles: f1 with: f2
  	"FFITestLibrary ffiTestDoubles: $A with: 65.0"
  	<cdecl: double 'ffiTestDoubles' (double double) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestFloats13:with:with:with:with:with:with:with:with:with:with:with:with: (in category 'atomic - floats') -----
+ ffiTestFloats13: f1 with: f2 with: f3 with: f4 with: f5 with: f6 with: f7 with: f8 with: f9 with: f10 with: f11 with: f12 with: f13
+ 
+ 	<cdecl: float 'ffiTestFloats13' (float float float float float float float float float float float float float) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestFloats14:with:with:with:with:with:with:with:with:with:with:with:with:with: (in category 'atomic - floats') -----
+ ffiTestFloats14: f1 with: f2 with: f3 with: f4 with: f5 with: f6 with: f7 with: f8 with: f9 with: f10 with: f11 with: f12 with: f13 with: f14
+ 
+ 	<cdecl: float 'ffiTestFloats14' (float float float float float float float float float float float float float float) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestFloats7:with:with:with:with:with:with: (in category 'atomic - floats') -----
+ ffiTestFloats7: f1 with: f2 with: f3 with: f4 with: f5 with: f6 with: f7
+ 
+ 	<cdecl: float 'ffiTestFloats7' (float float float float float float float) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestFloats:with: (in category 'atomic - floats') -----
- ----- Method: FFITestLibrary class>>ffiTestFloats:with: (in category 'primitives') -----
  ffiTestFloats: f1 with: f2
  	"FFITestLibrary ffiTestFloats: $A with: 65.0"
  	<cdecl: float 'ffiTestFloats' (float float) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInitSUfd:udSi2: (in category 'primitives') -----
- ffiTestInitSUfd: ufd udSi2: udSi2
- 	"FFITestLibrary FFITestInitSUfd: ... udSi2: .."
- 	<cdecl: FFITestSUfdUdSi2 'ffiTestInitSUfdUdSi2' (FFITestUfd FFITestUdSi2) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInitSUfd:ufi: (in category 'primitives') -----
- ffiTestInitSUfd: ufd ufi: ufi
- 	"FFITestLibrary ffiTestInitSUfd: ... ufi: .."
- 	<cdecl: FFITestSUfdUfi 'ffiTestInitSUfdUfi' (FFITestUfd FFITestUfi) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInitSUfdUdSi2:with: (in category 'structure - init') -----
+ ffiTestInitSUfdUdSi2: ufd with: udSi2
+ 	"FFITestLibrary ffiTestInitSUfdUdSi2: ... with: .."
+ 	<cdecl: FFITestSUfdUdSi2 'ffiTestInitSUfdUdSi2' (FFITestUfd FFITestUdSi2) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInitSUfdUfi:with: (in category 'structure - init') -----
+ ffiTestInitSUfdUfi: ufd with: ufi
+ 	"FFITestLibrary ffiTestInitSUfdUfi: ... with: .."
+ 	<cdecl: FFITestSUfdUfi 'ffiTestInitSUfdUfi' (FFITestUfd FFITestUfi) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInitUdSi2WithDouble: (in category 'primitives') -----
- ffiTestInitUdSi2WithDouble: d
- 	"FFITestLibrary ffiTestInitUdSi2WithDouble: 1.0"
- 	<cdecl: FFITestUdSi2 'ffiTestInitUdSi2_d' (double) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInitUdSi2WithInt:int: (in category 'primitives') -----
- ffiTestInitUdSi2WithInt: i1 int: i2
- 	"FFITestLibrary ffiTestInitUdSi2WithInt: 1 int: 2"
- 	<cdecl: FFITestUdSi2 'ffiTestInitUdSi2_ii' (long long) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInitUdSi2_d: (in category 'structure - init') -----
+ ffiTestInitUdSi2_d: d
+ 	"FFITestLibrary ffiTestInitUdSi2_d: 1.0"
+ 	<cdecl: FFITestUdSi2 'ffiTestInitUdSi2_d' (double) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInitUdSi2_ii:with: (in category 'structure - init') -----
+ ffiTestInitUdSi2_ii: i1 with: i2
+ 	"FFITestLibrary ffiTestInitUdSi2_ii: 1 with: 2"
+ 	<cdecl: FFITestUdSi2 'ffiTestInitUdSi2_ii' (int32_t int32_t) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInitUfdWithDouble: (in category 'primitives') -----
- ffiTestInitUfdWithDouble: d
- 	"FFITestLibrary ffiTestInitUfdWithDouble: 1.0"
- 	<cdecl: FFITestUfd 'ffiTestInitUfd_d' (double) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInitUfdWithFloat: (in category 'primitives') -----
- ffiTestInitUfdWithFloat: f
- 	"FFITestLibrary ffiTestInitUfdWithFloat: 1.0"
- 	<cdecl: FFITestUfd 'ffiTestInitUfd_f' (float) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInitUfd_d: (in category 'structure - init') -----
+ ffiTestInitUfd_d: d
+ 	"FFITestLibrary ffiTestInitUfd_d: 1.0"
+ 	<cdecl: FFITestUfd 'ffiTestInitUfd_d' (double) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInitUfd_f: (in category 'structure - init') -----
+ ffiTestInitUfd_f: f
+ 	"FFITestLibrary ffiTestInitUfd_f: 1.0"
+ 	<cdecl: FFITestUfd 'ffiTestInitUfd_f' (float) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInitUfiWithFloat: (in category 'primitives') -----
- ffiTestInitUfiWithFloat: f
- 	"FFITestLibrary ffiTestInitUfiWithFloat: 1.0"
- 	<cdecl: FFITestUfi 'ffiTestInitUfi_f' (float) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInitUfiWithInt: (in category 'primitives') -----
- ffiTestInitUfiWithInt: i
- 	"FFITestLibrary ffiTestInitUfiWithInt: 2"
- 	<cdecl: FFITestUfi 'ffiTestInitUfi_i' (long) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInitUfi_f: (in category 'structure - init') -----
+ ffiTestInitUfi_f: f
+ 	"FFITestLibrary ffiTestInitUfi_f: 1.0"
+ 	<cdecl: FFITestUfi 'ffiTestInitUfi_f' (float) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInitUfi_i: (in category 'structure - init') -----
+ ffiTestInitUfi_i: i
+ 	"FFITestLibrary ffiTestInitUfi_i: 2"
+ 	<cdecl: FFITestUfi 'ffiTestInitUfi_i' (long) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInt4IntAliasSum:with:with:with: (in category 'type alias') -----
+ ffiTestInt4IntAliasSum: c1 with: c2 with: c3 with: c4
+ 	"FFITestLibrary ffiTest4IntSum: 1 with: 2 with: 3 with: 4"
+ 	<cdecl: int 'ffiTest4IntSum' (FFITestIntAlias FFITestIntAlias FFITestIntAlias FFITestIntAlias) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestInt:with:with:with: (in category 'primitives - long vs. int') -----
- ffiTestInt: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary ffiTestInt: $A with: 65 with: 65.0 with: true"
- 	<cdecl: int 'ffiTestInts' (int int int int) module:'SqueakFFIPrims'>
- 	self flag: #ffiLongVsInt.
- 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestIntAlias4IntAliasSum:with:with:with: (in category 'type alias') -----
- ----- Method: FFITestLibrary class>>ffiTestIntAlias4IntAliasSum:with:with:with: (in category 'primitives - type alias') -----
  ffiTestIntAlias4IntAliasSum: c1 with: c2 with: c3 with: c4
  	"FFITestLibrary ffiTest4IntSum: 1 with: 2 with: 3 with: 4"
+ 	<cdecl: FFITestIntAlias 'ffiTest4IntSum' (FFITestIntAlias FFITestIntAlias FFITestIntAlias FFITestIntAlias) module:'SqueakFFIPrims'>
- 	<cdecl: int 'ffiTest4IntSum' (FFITestIntAlias FFITestIntAlias FFITestIntAlias FFITestIntAlias) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestIntAlias4IntSum:with:with:with: (in category 'type alias') -----
- ----- Method: FFITestLibrary class>>ffiTestIntAlias4IntSum:with:with:with: (in category 'primitives - type alias') -----
  ffiTestIntAlias4IntSum: c1 with: c2 with: c3 with: c4
  	"FFITestLibrary ffiTest4IntSum: 1 with: 2 with: 3 with: 4"
  	<cdecl: FFITestIntAlias 'ffiTest4IntSum' (int int int int) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInts8:with:with:with:with:with:with:with: (in category 'atomic - int32_t') -----
+ ffiTestInts8: c1 with: c2 with: c3 with: c4 with: c5 with: c6 with: c7 with: c8
+ 	"Always answers 42."
+ 	<cdecl: int32_t 'ffiTestInts8' (int32_t int32_t int32_t int32_t int32_t int32_t int32_t int32_t) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestInts:with:with:with: (in category 'atomic - int32_t') -----
+ ffiTestInts: c1 with: c2 with: c3 with: c4
+ 	"Adds c1 + c2"
+ 	<cdecl: int32_t 'ffiTestInts' (int32_t int32_t int32_t int32_t) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestLong:with:with:with: (in category 'primitives - long vs. int') -----
- ffiTestLong: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary ffiTestLong: $A with: 65 with: 65.0 with: true"
- 	<cdecl: long 'ffiTestInts' (long long long long) module:'SqueakFFIPrims'>
- 	self flag: #ffiLongVsInt.
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestLongLong8:with:with:with:with:with:with:with:with:with: (in category 'atomic - int64_t') -----
+ ffiTestLongLong8: char1 with: char2 with: char3 with: char4 with: char5 with: char6 with: char7 with: char8 with: long1 with: long2
+ 
+ 	<cdecl: longlong 'ffiTestLongLong8' (char char char char char char char char longlong longlong) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestLongLong8a1:with:with:with:with:with:with:with:with:with:with: (in category 'atomic - int64_t') -----
+ ffiTestLongLong8a1: char1 with: char2 with: char3 with: char4 with: char5 with: char6 with: char7 with: char8 with: char9 with: long1 with: long2
+ 
+ 	<cdecl: longlong 'ffiTestLongLong8a1' (char char char char char char char char char longlong longlong) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestLongLong8a2:with:with:with:with:with:with:with:with:with:with:with: (in category 'atomic - int64_t') -----
+ ffiTestLongLong8a2: char1 with: char2 with: char3 with: char4 with: char5 with: char6 with: char7 with: char8 with: char9 with: char10 with: long1 with: long2
+ 
+ 	<cdecl: longlong 'ffiTestLongLong8a2' (char char char char char char char char char char longlong longlong) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestLongLong:with: (in category 'atomic - int64_t') -----
- ----- Method: FFITestLibrary class>>ffiTestLongLong:with: (in category 'primitives') -----
  ffiTestLongLong: long1 with: long2
  	"FFITestLibrary ffiTestLongLong: 3 with: 4"
  	<cdecl: longlong 'ffiTestLongLong' (longlong longlong) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestLongLongA1:with:with: (in category 'primitives') -----
- ffiTestLongLongA1: byte with: long1 with: long2
- 	"FFITestLibrary ffiTestLongLongA1: 3 with: 4 with: 5"
- 	<cdecl: longlong 'ffiTestLongLonga1' (char longlong longlong) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestLongLongA3:with:with: (in category 'primitives') -----
- ffiTestLongLongA3: byte1 with: long1 with: byte2
- 	"FFITestLibrary ffiTestLongLongA3: 3 with: 4 with: 5"
- 	<cdecl: longlong 'ffiTestLongLonga3' (char longlong char) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestLongLonga1:with:with: (in category 'atomic - int64_t') -----
+ ffiTestLongLonga1: byte with: long1 with: long2
+ 	"FFITestLibrary ffiTestLongLongA1: 3 with: 4 with: 5"
+ 	<cdecl: longlong 'ffiTestLongLonga1' (char longlong longlong) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestLongLonga2:with:with:with: (in category 'atomic - int64_t') -----
+ ffiTestLongLonga2: byte1 with: byte2 with: long1 with: long2
+ 
+ 	<cdecl: longlong 'ffiTestLongLonga2' (char char longlong longlong) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestLongLonga3:with:with: (in category 'atomic - int64_t') -----
+ ffiTestLongLonga3: byte1 with: long1 with: byte2
+ 	"FFITestLibrary ffiTestLongLonga3: 3 with: 4 with: 5"
+ 	<cdecl: longlong 'ffiTestLongLonga3' (char longlong char) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestLongLongs8:with:with:with:with:with:with:with: (in category 'atomic - int64_t') -----
+ ffiTestLongLongs8: long1 with: long2 with: long3 with: long4 with: long5 with: long6 with: long7 with: long8
+ 	"Always answers 42."
+ 	<cdecl: longlong 'ffiTestLongLongs8' (longlong longlong longlong longlong longlong longlong longlong longlong) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestMixedDoublesAndLongs:with:with:with:with:with:with:with:with:with:with:with:with:with:with: (in category 'atomic') -----
+ ffiTestMixedDoublesAndLongs: arg1 with: arg2 with: arg3 with: arg4 with: arg5 with: arg6 with: arg7 with: arg8 with: arg9 with: arg10 with: arg11 with: arg12 with: arg13 with: arg14 with: arg15 "with: arg16 with: arg17 with: arg18 with: arg19 with: arg20"
+  
+ 	<cdecl: double 'ffiTestMixedDoublesAndLongs' (double c_long double c_long double c_long double c_long double c_long double c_long double c_long double c_long double c_long double c_long) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestMixedDoublesIntAndStruct:d:d:d:d:d:d:d:d:i:s: (in category 'primitives') -----
- ffiTestMixedDoublesIntAndStruct: f1 d: f2 d: f3 d: f4 d: f5 d: f6 d: f7 d: f8 d: f9 i: i1 s: s1
- 	"FFITestLibrary ffiTestMixedDoublesIntAndStruct: 1.0 d: 2.0 d: 3.0 d: 4.0 d: 5.0 d: 6.0 d: 7.0 d: 8.0 d: 9.0 i: 42
- 		s: (FFITestPoint4 new x: 3; y: 4; z: 5; w:6)"
- 	<cdecl: double 'ffiTestMixedDoublesIntAndStruct' (double double double double double double double double double long FFITestPoint4) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestMixedDoublesIntAndStruct:with:with:with:with:with:with:with:with:with:with: (in category 'structure') -----
+ ffiTestMixedDoublesIntAndStruct: f1 with: f2 with: f3 with: f4 with: f5 with: f6 with: f7 with: f8 with: f9 with: i1 with: s1
+ 	"
+ 	FFITestLibrary ffiTestMixedDoublesIntAndStruct: 1.0
+ 		with: 2.0 with: 3.0 with: 4.0 with: 5.0
+ 		with: 6.0 with: 7.0 with: 8.0 with: 9.0 with: 42
+ 		with: (FFITestPoint4 new x: 3; y: 4; z: 5; w:6)
+ 	"
+ 	<cdecl: double 'ffiTestMixedDoublesIntAndStruct' (double double double double double double double double double long FFITestPoint4) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestMixedFloatsAndDouble:with:with:with: (in category 'atomic') -----
- ----- Method: FFITestLibrary class>>ffiTestMixedFloatsAndDouble:with:with:with: (in category 'primitives') -----
  ffiTestMixedFloatsAndDouble: f1 with: d1 with: f2 with: f3
  	"FFITestLibrary ffiTestMixedFloatsAndDouble: 1.2 with: 3.4 with: 5.6 with: 7.8"
  	<cdecl: double 'ffiTestMixedFloatsAndDouble' (float double float float) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestMixedIntAndStruct2:with: (in category 'structure') -----
- ----- Method: FFITestLibrary class>>ffiTestMixedIntAndStruct2:with: (in category 'primitives') -----
  ffiTestMixedIntAndStruct2: i with: pt4
  	"FFITestLibrary ffiTestMixedIntAndStruct2: 2 with: (FFITestPoint4 new x: 3; y: 4; z: 5; w:6)"
+ 	<cdecl: int32_t 'ffiTestMixedIntAndStruct2' (int32_t FFITestPoint4) module:'SqueakFFIPrims'>
- 	<cdecl: long 'ffiTestMixedIntAndStruct2' (long FFITestPoint4) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestMixedIntAndStruct3:with: (in category 'structure') -----
- ----- Method: FFITestLibrary class>>ffiTestMixedIntAndStruct3:with: (in category 'primitives') -----
  ffiTestMixedIntAndStruct3: i with: anFFISmallStruct1
  	"FFITestLibrary ffiTestMixedIntAndStruct3: 2 with: (FFISmallStruct1 new x: 3; y: 4)"
+ 	<cdecl: int32_t 'ffiTestMixedIntAndStruct3' (int32_t FFISmallStruct1) module:'SqueakFFIPrims'>
- 	<cdecl: long 'ffiTestMixedIntAndStruct3' (long FFISmallStruct1) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestMixedIntAndStruct:with:with: (in category 'structure') -----
- ----- Method: FFITestLibrary class>>ffiTestMixedIntAndStruct:with:with: (in category 'primitives') -----
  ffiTestMixedIntAndStruct: i with: pt1 with: pt2
  	"FFITestLibrary ffiTestMixedIntAndStruct: 2 with: (FFITestPoint2 new x: 3; y: 4) with: (FFITestPoint2 new x: 5; y: 6)"
+ 	<cdecl: int32_t 'ffiTestMixedIntAndStruct' (int32_t FFITestPoint2 FFITestPoint2) module:'SqueakFFIPrims'>
- 	<cdecl: long 'ffiTestMixedIntAndStruct' (long FFITestPoint2 FFITestPoint2) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestPoint2:with: (in category 'primitives') -----
- ffiTestPoint2: pt1 with: pt2
- 	<cdecl: FFITestPoint2 'ffiTestStruct64' (FFITestPoint2 FFITestPoint2) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestPoint4:with: (in category 'primitives') -----
- ffiTestPoint4: pt1 with: pt2
- 	<cdecl: FFITestPoint4 'ffiTestStructBig' (FFITestPoint4 FFITestPoint4) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestPointers:with: (in category 'structure - points') -----
- ----- Method: FFITestLibrary class>>ffiTestPointers:with: (in category 'primitives') -----
  ffiTestPointers: pt1 with: pt2
+ 	"Allocates the result. Needs to be free'd after calling."
  	<cdecl: FFITestPoint4* 'ffiTestPointers' (FFITestPoint4* FFITestPoint4*) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSSdi5 (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSSdi5 (in category 'primitives') -----
  ffiTestReturnSSdi5
  	"FFITestLibrary ffiTestReturnSSdi5"
  	<cdecl: FFITestSSdi5 'ffiTestReturnSSdi5' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSd2 (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSd2 (in category 'primitives') -----
  ffiTestReturnSd2
  	"FFITestLibrary ffiTestReturnSd2"
  	<cdecl: FFITestSd2 'ffiTestReturnSd2' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSdi (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSdi (in category 'primitives') -----
  ffiTestReturnSdi
  	"FFITestLibrary ffiTestReturnSdi"
  	<cdecl: FFITestSdi 'ffiTestReturnSdi' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSf2 (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSf2 (in category 'primitives') -----
  ffiTestReturnSf2
  	"FFITestLibrary ffiTestReturnSf2"
  	<cdecl: FFITestSf2 'ffiTestReturnSf2' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSf2d (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSf2d (in category 'primitives') -----
  ffiTestReturnSf2d
  	"FFITestLibrary ffiTestReturnSf2d"
  	<cdecl: FFITestSf2d 'ffiTestReturnSf2d' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSf4 (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSf4 (in category 'primitives') -----
  ffiTestReturnSf4
  	"FFITestLibrary ffiTestReturnSf4"
  	<cdecl: FFITestSf4 'ffiTestReturnSf4' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSfd (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSfd (in category 'primitives') -----
  ffiTestReturnSfd
  	"FFITestLibrary ffiTestReturnSfd"
  	<cdecl: FFITestSfd 'ffiTestReturnSfd' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSfdf (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSfdf (in category 'primitives') -----
  ffiTestReturnSfdf
  	"FFITestLibrary ffiTestReturnSfdf"
  	<cdecl: FFITestSfdf 'ffiTestReturnSfdf' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSfi (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSfi (in category 'primitives') -----
  ffiTestReturnSfi
  	"FFITestLibrary ffiTestReturnSfi"
  	<cdecl: FFITestSfi 'ffiTestReturnSfi' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSi2 (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSi2 (in category 'primitives') -----
  ffiTestReturnSi2
  	"FFITestLibrary ffiTestReturnSi2"
  	<cdecl: FFITestSi2 'ffiTestReturnSi2' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSl2 (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSl2 (in category 'primitives') -----
  ffiTestReturnSl2
  	"FFITestLibrary ffiTestReturnSl2"
  	<cdecl: FFITestSl2 'ffiTestReturnSl2' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSs2 (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSs2 (in category 'primitives') -----
  ffiTestReturnSs2
  	"FFITestLibrary ffiTestReturnSs2"
  	<cdecl: FFITestSs2 'ffiTestReturnSs2' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSs2i (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSs2i (in category 'primitives') -----
  ffiTestReturnSs2i
  	"FFITestLibrary ffiTestReturnSs2i"
  	<cdecl: FFITestSs2i 'ffiTestReturnSs2i' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSs4 (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSs4 (in category 'primitives') -----
  ffiTestReturnSs4
  	"FFITestLibrary ffiTestReturnSs4"
  	<cdecl: FFITestSs4 'ffiTestReturnSs4' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSsSsf (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSsSsf (in category 'primitives') -----
  ffiTestReturnSsSsf
  	"FFITestLibrary ffiTestReturnSsSsf"
  	<cdecl: FFITestSsSsf 'ffiTestReturnSsSsf' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSsSsi (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSsSsi (in category 'primitives') -----
  ffiTestReturnSsSsi
  	"FFITestLibrary ffiTestReturnSsSsi"
  	<cdecl: FFITestSsSsi 'ffiTestReturnSsSsi' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSsf (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSsf (in category 'primitives') -----
  ffiTestReturnSsf
  	"FFITestLibrary ffiTestReturnSsf"
  	<cdecl: FFITestSsf 'ffiTestReturnSsf' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSsi (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSsi (in category 'primitives') -----
  ffiTestReturnSsi
  	"FFITestLibrary ffiTestReturnSsi"
  	<cdecl: FFITestSsi 'ffiTestReturnSsi' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSsis (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSsis (in category 'primitives') -----
  ffiTestReturnSsis
  	"FFITestLibrary ffiTestReturnSsis"
  	<cdecl: FFITestSsis 'ffiTestReturnSsis' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSslf (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSslf (in category 'primitives') -----
  ffiTestReturnSslf
  	"FFITestLibrary ffiTestReturnSslf"
  	<cdecl: FFITestSslf 'ffiTestReturnSslf' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestReturnSsls (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestReturnSsls (in category 'primitives') -----
  ffiTestReturnSsls
  	"FFITestLibrary ffiTestReturnSsls"
  	<cdecl: FFITestSsls 'ffiTestReturnSsls' () module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestShort:with:with:with: (in category 'primitives') -----
- ffiTestShort: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary ffiTestShort: $A with: 65 with: 65.0 with:1"
- 	<cdecl: short 'ffiTestShorts' (short short short short) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestShorts:with:with:with: (in category 'atomic - int16_t') -----
+ ffiTestShorts: c1 with: c2 with: c3 with: c4
+ 	"Answers c1 + c2.
+ 	FFITestLibrary ffiTestShorts: 1 with: 2 with: 3 with: 4"
+ 	<cdecl: short 'ffiTestShorts' (short short short short) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestSmallStructReturn (in category 'structure - return') -----
- ----- Method: FFITestLibrary class>>ffiTestSmallStructReturn (in category 'primitives') -----
  ffiTestSmallStructReturn
  	"FFITestLibrary ffiTestSmallStructReturn"
  	<cdecl: FFISmallStruct1 'ffiTestSmallStructReturn' (void) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestStruct64:with: (in category 'structure - points') -----
+ ffiTestStruct64: pt1 with: pt2
+ 	"pt1 + pt2"
+ 	<cdecl: FFITestPoint2 'ffiTestStruct64' (FFITestPoint2 FFITestPoint2) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestStructBig:with: (in category 'structure - points') -----
+ ffiTestStructBig: pt1 with: pt2
+ 	"pt1 + pt2"
+ 	<cdecl: FFITestPoint4 'ffiTestStructBig' (FFITestPoint4 FFITestPoint4) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestStructBigger:with: (in category 'structure - points') -----
+ ffiTestStructBigger: pt1 with: pt2
+ 	"Copies the values of pt1 to x, y, z, w and pt2 to r, s, t, u in the resulting struct."
+ 	<cdecl: FFITestBiggerStruct 'ffiTestStructBigger' (FFITestPoint4 FFITestPoint4) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumOfDoubleFromSUfdUdsi2: (in category 'primitives') -----
- ffiTestSumOfDoubleFromSUfdUdsi2: sUfdUfi
- 	"FFITestLibrary ffiTestSumOfFloatFromSUfdUdSi2: (FFITestLibrary ...)"
- 	<cdecl: double 'ffiTestSumSUfdUdSi2_d' (FFITestSUfdUdSi2) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumOfFloatFromSUfdUfi: (in category 'primitives') -----
- ffiTestSumOfFloatFromSUfdUfi: sUfdUfi
- 	"FFITestLibrary ffiTestSumOfFloatFromSUfdUfi: (FFITestLibrary ...)"
- 	<cdecl: double 'ffiTestSumSUfdUfi_f' (FFITestSUfdUfi) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSSdi5: (in category 'structure - sums') -----
+ ffiTestSumSSdi5: structSdi5
+ 	"
+ 	FFITestLibrary ffiTestSumSSdi5: FFITestLibrary ffiTestReturnSSdi5
+ 	"
+ 	<cdecl: double 'ffiTestSumSSdi5' (FFITestSSdi5) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSUfdUdSi2_d: (in category 'structure - sums') -----
+ ffiTestSumSUfdUdSi2_d: sUfdUfi
+ 	"
+ 	FFITestLibrary ffiTestSumOfFloatFromSUfdUdSi2: (FFITestLibrary ...)
+ 	"
+ 	<cdecl: double 'ffiTestSumSUfdUdSi2_d' (FFITestSUfdUdSi2) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSUfdUfi_f: (in category 'structure - sums') -----
+ ffiTestSumSUfdUfi_f: sUfdUfi
+ 	"
+ 	FFITestLibrary ffiTestSumSUfdUfi_f: (FFITestLibrary ...)
+ 	"
+ 	<cdecl: double 'ffiTestSumSUfdUfi_f' (FFITestSUfdUfi) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestSumSdi: (in category 'structure - sums') -----
- ----- Method: FFITestLibrary class>>ffiTestSumSdi: (in category 'primitives') -----
  ffiTestSumSdi: sdi
+ 	"
+ 	FFITestLibrary ffiTestSumSdi: FFITestLibrary ffiTestReturnSdi
+ 	"
- 	"FFITestLibrary ffiTestSumSdi: FFITestLibrary ffiTestReturnSdi"
  	<cdecl: double 'ffiTestSumSdi' (FFITestSdi) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumSdi:sdi: (in category 'primitives') -----
- ffiTestSumSdi: sdi1 sdi: sdi2
- 	"FFITestLibrary ffiTestSumSdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi"
- 	<cdecl: double 'ffiTestSumSdi_2' (FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumSdi:sdi:sdi:sdi: (in category 'primitives') -----
- ffiTestSumSdi: sdi1 sdi: sdi2 sdi: sdi3 sdi: sdi4
- 	"FFITestLibrary ffiTestSumSdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi"
- 	<cdecl: double 'ffiTestSumSdi_4' (FFITestSdi FFITestSdi FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSdi_2:with: (in category 'structure - sums') -----
+ ffiTestSumSdi_2: sdi1 with: sdi2
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumSdi_2: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 	"
+ 	<cdecl: double 'ffiTestSumSdi_2' (FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSdi_4:with:with:with: (in category 'structure - sums') -----
+ ffiTestSumSdi_4: sdi1 with: sdi2 with: sdi3 with: sdi4
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumSdi_4: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 	"
+ 	<cdecl: double 'ffiTestSumSdi_4' (FFITestSdi FFITestSdi FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestSumSfd: (in category 'structure - sums') -----
- ----- Method: FFITestLibrary class>>ffiTestSumSfd: (in category 'primitives') -----
  ffiTestSumSfd: sfd
+ 	"
+ 	FFITestLibrary ffiTestSumSfd: FFITestLibrary ffiTestReturnSfd
+ 	"
- 	"FFITestLibrary ffiTestSumSfd: FFITestLibrary ffiTestReturnSfd"
  	<cdecl: double 'ffiTestSumSfd' (FFITestSfd) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumSfd:sfd: (in category 'primitives') -----
- ffiTestSumSfd: sfd1 sfd: sfd2
- 	"FFITestLibrary ffiTestSumSfd: FFITestLibrary ffiTestReturnSfd sfd: FFITestLibrary ffiTestReturnSfd"
- 	<cdecl: double 'ffiTestSumSfd_2' (FFITestSfd FFITestSfd) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumSfd:sfd:sfd:sfd: (in category 'primitives') -----
- ffiTestSumSfd: sfd1 sfd: sfd2 sfd: sfd3 sfd: sfd4
- 	"FFITestLibrary ffiTestSumSfd: FFITestLibrary ffiTestReturnSfd sfd: FFITestLibrary ffiTestReturnSfd sfd: FFITestLibrary ffiTestReturnSfd sfd: FFITestLibrary ffiTestReturnSfd"
- 	<cdecl: double 'ffiTestSumSfd_4' (FFITestSfd FFITestSfd FFITestSfd FFITestSfd) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSfd_2:with: (in category 'structure - sums') -----
+ ffiTestSumSfd_2: sfd1 with: sfd2
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumSfd_2: FFITestLibrary ffiTestReturnSfd
+ 		with: FFITestLibrary ffiTestReturnSfd
+ 	"
+ 	<cdecl: double 'ffiTestSumSfd_2' (FFITestSfd FFITestSfd) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSfd_4:with:with:with: (in category 'structure - sums') -----
+ ffiTestSumSfd_4: sfd1 with: sfd2 with: sfd3 with: sfd4
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumSfd_4: FFITestLibrary ffiTestReturnSfd
+ 		with: FFITestLibrary ffiTestReturnSfd
+ 		with: FFITestLibrary ffiTestReturnSfd
+ 		with: FFITestLibrary ffiTestReturnSfd				
+ 	"
+ 	<cdecl: double 'ffiTestSumSfd_4' (FFITestSfd FFITestSfd FFITestSfd FFITestSfd) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestSumSslf: (in category 'structure - sums') -----
- ----- Method: FFITestLibrary class>>ffiTestSumSslf: (in category 'primitives') -----
  ffiTestSumSslf: sslf
+ 	"
+ 	FFITestLibrary ffiTestSumSslf: FFITestLibrary ffiTestReturnSslf
+ 	"
- 	"FFITestLibrary ffiTestSumSslf: FFITestLibrary ffiTestReturnSslf"
  	<cdecl: double 'ffiTestSumSslf' (FFITestSslf) module:'SqueakFFIPrims'>
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumSslf:sslf: (in category 'primitives') -----
- ffiTestSumSslf: sslf1 sslf: sslf2
- 	"FFITestLibrary ffiTestSumSslf: FFITestLibrary ffiTestReturnSslf sslf: FFITestLibrary ffiTestReturnSslf"
- 	<cdecl: double 'ffiTestSumSslf_2' (FFITestSslf FFITestSslf) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumSslf:sslf:sslf:sslf: (in category 'primitives') -----
- ffiTestSumSslf: sslf1 sslf: sslf2 sslf: sslf3 sslf: sslf4
- 	"FFITestLibrary ffiTestSumSslf: FFITestLibrary ffiTestReturnSslf sslf: FFITestLibrary ffiTestReturnSslf sslf: FFITestLibrary ffiTestReturnSslf sslf: FFITestLibrary ffiTestReturnSslf"
- 	<cdecl: double 'ffiTestSumSslf_4' (FFITestSslf FFITestSslf FFITestSslf FFITestSslf) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSslf_2:with: (in category 'structure - sums') -----
+ ffiTestSumSslf_2: sslf1 with: sslf2
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumSslf_2: FFITestLibrary ffiTestReturnSslf
+ 		with: FFITestLibrary ffiTestReturnSslf		
+ 	"
+ 	<cdecl: double 'ffiTestSumSslf_2' (FFITestSslf FFITestSslf) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumSslf_4:with:with:with: (in category 'structure - sums') -----
+ ffiTestSumSslf_4: sslf1 with: sslf2 with: sslf3 with: sslf4
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumSslf_4: FFITestLibrary ffiTestReturnSslf
+ 		with: FFITestLibrary ffiTestReturnSslf
+ 		with: FFITestLibrary ffiTestReturnSslf	
+ 		with: FFITestLibrary ffiTestReturnSslf	
+ 	"
+ 	<cdecl: double 'ffiTestSumSslf_4' (FFITestSslf FFITestSslf FFITestSslf FFITestSslf) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumStructSdi5: (in category 'primitives') -----
- ffiTestSumStructSdi5: structSdi5
- 	"FFITestLibrary ffiTestSumStructSdi5: FFITestLibrary ffiTestReturnSSdi5"
- 	<cdecl: double 'ffiTestSumSSdi5' (FFITestSSdi5) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumd:i:withSdi:sdi:sdi:sdi: (in category 'primitives') -----
- ffiTestSumd: aDouble i: anInt withSdi: sdi1 sdi: sdi2 sdi: sdi3 sdi: sdi4
- 	"FFITestLibrary ffiTestSumd: 4.0 i: 3 withSdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi"
- 	<cdecl: double 'ffiTestSumdiWithSdi_4' (double long FFITestSdi FFITestSdi FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumd:withSdi:sdi:sdi:sdi: (in category 'primitives') -----
- ffiTestSumd: aDouble withSdi: sdi1 sdi: sdi2 sdi: sdi3 sdi: sdi4
- 	"FFITestLibrary ffiTestSumd: 4.0 withSdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi"
- 	<cdecl: double 'ffiTestSumdWithSdi_4' (double FFITestSdi FFITestSdi FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumdWithSdi_4:with:with:with:with: (in category 'structure - sums') -----
+ ffiTestSumdWithSdi_4: aDouble with: sdi1 with: sdi2 with: sdi3 with: sdi4
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumdWithSdi_4: 4.0
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 	"
+ 	<cdecl: double 'ffiTestSumdWithSdi_4' (double FFITestSdi FFITestSdi FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumdiWithSdi_4:with:with:with:with:with: (in category 'structure - sums') -----
+ ffiTestSumdiWithSdi_4: aDouble with: anInt with: sdi1 with: sdi2 with: sdi3 with: sdi4
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumdiWithSdi_4: 4.0
+ 		with: 3
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 	"
+ 	<cdecl: double 'ffiTestSumdiWithSdi_4' (double long FFITestSdi FFITestSdi FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumf:withSfd:sfd:sfd:sfd: (in category 'primitives') -----
- ffiTestSumf: aFloat withSfd: sfd1 sfd: sfd2 sfd: sfd3 sfd: sfd4
- 	"FFITestLibrary ffiTestSumf: 0.5 withSfd: FFITestLibrary ffiTestReturnSfd sfd: FFITestLibrary ffiTestReturnSfd sfd: FFITestLibrary ffiTestReturnSfd sfd: FFITestLibrary ffiTestReturnSfd"
- 	<cdecl: double 'ffiTestSumfWithSfd_4' (float FFITestSfd FFITestSfd FFITestSfd FFITestSfd) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumfWithSfd_4:with:with:with:with: (in category 'structure - sums') -----
+ ffiTestSumfWithSfd_4: aFloat with: sfd1 with: sfd2 with: sfd3 with: sfd4
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumf: 0.5
+ 		with: FFITestLibrary ffiTestReturnSfd
+ 		with: FFITestLibrary ffiTestReturnSfd
+ 		with: FFITestLibrary ffiTestReturnSfd
+ 		with: FFITestLibrary ffiTestReturnSfd
+ 	"
+ 	<cdecl: double 'ffiTestSumfWithSfd_4' (float FFITestSfd FFITestSfd FFITestSfd FFITestSfd) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestSumi:withSdi:sdi:sdi:sdi: (in category 'primitives') -----
- ffiTestSumi: anInt withSdi: sdi1 sdi: sdi2 sdi: sdi3 sdi: sdi4
- 	"FFITestLibrary ffiTestSumi: 3 withSdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi sdi: FFITestLibrary ffiTestReturnSdi"
- 	<cdecl: double 'ffiTestSumiWithSdi_4' (long FFITestSdi FFITestSdi FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
- 	^self externalCallFailed!

Item was added:
+ ----- Method: FFITestLibrary class>>ffiTestSumiWithSdi_4:with:with:with:with: (in category 'structure - sums') -----
+ ffiTestSumiWithSdi_4: anInt with: sdi1 with: sdi2 with: sdi3 with: sdi4
+ 	"
+ 	FFITestLibrary
+ 		ffiTestSumiWithSdi_4: 3
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 		with: FFITestLibrary ffiTestReturnSdi
+ 	"
+ 	<cdecl: double 'ffiTestSumiWithSdi_4' (int32_t FFITestSdi FFITestSdi FFITestSdi FFITestSdi) module:'SqueakFFIPrims'>
+ 	^self externalCallFailed!

Item was changed:
+ ----- Method: FFITestLibrary class>>ffiTestUint:with:with:with: (in category 'atomic - uint32_t') -----
- ----- Method: FFITestLibrary class>>ffiTestUint:with:with:with: (in category 'primitives - long vs. int') -----
  ffiTestUint: c1 with: c2 with: c3 with: c4
+ 	"Answers c1 + c2. Repurpose ffiTestInts to check uint32_t range."
+ 	<cdecl: int32_t 'ffiTestInts' (uint32_t uint32_t uint32_t uint32_t) module:'SqueakFFIPrims'>
- 	"FFITestLibrary ffiTestUint: 3103854339 with: 3103854339 with: 3103854339 with: 3103854339"
- 	<cdecl: int 'ffiTestInts' (uint uint uint uint) module:'SqueakFFIPrims'>
- 	self flag: #ffiLongVsInt.
  	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary class>>ffiTestUlong:with:with:with: (in category 'primitives - long vs. int') -----
- ffiTestUlong: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary ffiTestUlong: 3103854339 with: 3103854339 with: 3103854339 with: 3103854339"
- 	<cdecl: long 'ffiTestInts' (ulong ulong ulong ulong) module:'SqueakFFIPrims'>
- 	self flag: #ffiLongVsInt.
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary>>ffiPrintString: (in category 'primitives') -----
- ffiPrintString: aString
- 	"FFITestLibrary new ffiPrintString: 'Hello'"
- 	<cdecl: char* 'ffiPrintString' (char *)>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary>>ffiTestChar:with:with:with: (in category 'primitives') -----
- ffiTestChar: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary new ffiTestChar: $A with: 65 with: 65.0 with: true"
- 	<cdecl: char 'ffiTestChars' (char char char char)>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary>>ffiTestDoubles:with: (in category 'primitives') -----
- ffiTestDoubles: f1 with: f2
- 	"FFITestLibrary new ffiTestDoubles: $A with: 65.0"
- 	<cdecl: double 'ffiTestDoubles' (double double)>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary>>ffiTestFloats:with: (in category 'primitives') -----
- ffiTestFloats: f1 with: f2
- 	"FFITestLibrary new ffiTestFloats: $A with: 65.0"
- 	<cdecl: float 'ffiTestFloats' (float float)>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary>>ffiTestInt:with:with:with: (in category 'primitives') -----
- ffiTestInt: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary new ffiTestInt: $A with: 65 with: 65.0 with: $A"
- 	<cdecl: long 'ffiTestInts' (long long long long)>
- 	^self externalCallFailed!

Item was removed:
- ----- Method: FFITestLibrary>>ffiTestShort:with:with:with: (in category 'primitives') -----
- ffiTestShort: c1 with: c2 with: c3 with: c4
- 	"FFITestLibrary new ffiTestShort: $A with: 65 with: 65.0 with: $A"
- 	<cdecl: short 'ffiTestShorts' (short short short short)>
- 	^self externalCallFailed!

Item was changed:
  ----- Method: FFITestMisalignedCompoundStruct class>>fields (in category 'field definition') -----
  fields
  	"FFITestMisalignedCompoundStruct defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
- 		(s1	#short)
  		(s2	'FFITestMisalignedStruct')
  	)!

Item was changed:
  ----- Method: FFITestMisalignedStruct class>>fields (in category 'field definition') -----
  fields
  	"FFITestMisalignedStruct defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(i1	'int32_t')
- 		(s1	#short)
- 		(i1	#long)
  	)!

Item was changed:
  ----- Method: FFITestPoint2 class>>fields (in category 'field definition') -----
  fields
  	"FFITestPoint2 defineFields"
  	^#(
+ 		(x	'int32_t')
+ 		(y	'int32_t')
- 		(x	'long')
- 		(y	'long')
  	)!

Item was added:
+ ----- Method: FFITestPoint2>>asPoint (in category 'converting') -----
+ asPoint
+ 
+ 	^ self x @ self y!

Item was added:
+ ----- Method: FFITestPoint2>>setX:setY: (in category 'initialization') -----
+ setX: xValue setY: yValue.
+ 
+ 	self x: xValue.
+ 	self y: yValue.!

Item was changed:
  ----- Method: FFITestPoint4 class>>fields (in category 'field definition') -----
  fields
  	"FFITestPoint4 defineFields"
  	^#(
+ 		(x	'int32_t')
+ 		(y	'int32_t')
+ 		(z	'int32_t')
+ 		(w	'int32_t')
- 		(x	'long')
- 		(y	'long')
- 		(z	'long')
- 		(w	'long')
  	)!

Item was changed:
  ----- Method: FFITestSdi class>>fields (in category 'field definition') -----
  fields
  	"FFITestSdi defineFields"
  	^#(
  		(d1	'double')
+ 		(i2	'int32_t')
- 		(i2	'long')
  	)!

Item was changed:
  ----- Method: FFITestSfi class>>fields (in category 'field definition') -----
  fields
  	"FFITestSfi defineFields"
  	^#(
  		(f1	'float')
+ 		(i2	'int32_t')
- 		(i2	'long')
  	)!

Item was changed:
  ----- Method: FFITestSi2 class>>fields (in category 'field definition') -----
  fields
  	"FFITestSi2 defineFields"
  	^#(
+ 		(i1	'int32_t')
+ 		(i2	'int32_t')
- 		(i1	'long')
- 		(i2	'long')
  	)!

Item was changed:
  ----- Method: FFITestSl2 class>>fields (in category 'field definition') -----
  fields
  	"FFITestSl2 defineFields"
  	^#(
+ 		(l1	'int64_t') "longlong"
+ 		(l2	'int64_t') "longlong"
- 		(l1	'longlong')
- 		(l2	'longlong')
  	)!

Item was changed:
  ----- Method: FFITestSs2 class>>fields (in category 'field definition') -----
  fields
  	"FFITestSs2 defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(s2	'int16_t') "short"
- 		(s1	'short')
- 		(s2	'short')
  	)!

Item was changed:
  ----- Method: FFITestSs2i class>>fields (in category 'field definition') -----
  fields
  	"FFITestSs2i defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(s2	'int16_t') "short"
+ 		(i3	'int32_t')
- 		(s1	'short')
- 		(s2	'short')
- 		(i3	'long')
  	)!

Item was changed:
  ----- Method: FFITestSs4 class>>fields (in category 'field definition') -----
  fields
  	"FFITestSs4 defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(s2	'int16_t') "short"
+ 		(s3	'int16_t') "short"
+ 		(s4	'int16_t') "short"
- 		(s1	'short')
- 		(s2	'short')
- 		(s3	'short')
- 		(s4	'short')
  	)!

Item was changed:
  ----- Method: FFITestSsSsf class>>fields (in category 'field definition') -----
  fields
  	"FFITestSsSsf defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
- 		(s1	'short')
  		(ssf2	'FFITestSsf')
  	)!

Item was changed:
  ----- Method: FFITestSsSsi class>>fields (in category 'field definition') -----
  fields
  	"FFITestSsSsi defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(ssi2	FFITestSsi)
- 		(s1	'short')
- 		(ssi2	'FFITestSsi')
  	)!

Item was changed:
  ----- Method: FFITestSsf class>>fields (in category 'field definition') -----
  fields
  	"FFITestSsf defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
- 		(s1	'short')
  		(f2	'float')
  	)!

Item was changed:
  ----- Method: FFITestSsi class>>fields (in category 'field definition') -----
  fields
  	"FFITestSsi defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(i2	'int32_t')
- 		(s1	'short')
- 		(i2	'long')
  	)!

Item was changed:
  ----- Method: FFITestSsis class>>fields (in category 'field definition') -----
  fields
  	"FFITestSsis defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(i2	'int32_t')
+ 		(s3	'int16_t') "short"
- 		(s1	'short')
- 		(i2	'long')
- 		(s3	'short')
  	)!

Item was changed:
  ----- Method: FFITestSslf class>>fields (in category 'field definition') -----
  fields
  	"FFITestSslf defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(l2	'int64_t') "longlong"
- 		(s1	'short')
- 		(l2	'longlong')
  		(f3	'float')
  	)!

Item was changed:
  ----- Method: FFITestSsls class>>fields (in category 'field definition') -----
  fields
  	"FFITestSsls defineFields"
  	^#(
+ 		(s1	'int16_t') "short"
+ 		(l2	'int64_t') "longlong"
+ 		(s3	'int16_t') "short"
- 		(s1	'short')
- 		(l2	'longlong')
- 		(s3	'short')
  	)!

Item was changed:
  ----- Method: FFITestUfi class>>fields (in category 'field definition') -----
  fields
  	"FFITestUfi defineFields"
  	^#(
  		(f1	'float')
+ 		(i1	'int32_t')
- 		(i1	'long')
  	)!

Item was changed:
  ----- Method: FFITypeNameTests>>testAtomicChar (in category 'tests') -----
  testAtomicChar
  
  	self
  		flag: #ffiLongVsInt;
+ 		assert: (self argTypesAt: #ffiTestChars:with:with:with:)
- 		assert: (self argTypesAt: #ffiTestChar:with:with:with:)
  		equals: (Array new: 5 withAll: ExternalType char).!

Item was changed:
  ----- Method: FFITypeNameTests>>testAtomicInt (in category 'tests') -----
  testAtomicInt
  
  	self
  		flag: #ffiLongVsInt;
+ 		assert: (self argTypesAt: #ffiTestInts:with:with:with:)
- 		assert: (self argTypesAt: #ffiTestInt:with:with:with:)
  		equals: (Array new: 5 withAll: ExternalType int).!

Item was changed:
  ----- Method: FFITypeNameTests>>testAtomicLong (in category 'tests') -----
  testAtomicLong
  
  	self
  		flag: #ffiLongVsInt;
+ 		assert: (self argTypesAt: #ffiTestInts:with:with:with:)
- 		assert: (self argTypesAt: #ffiTestLong:with:with:with:)
  		equals: (Array new: 5 withAll: ExternalType long).!

Item was changed:
  ----- Method: FFITypeNameTests>>testAtomicUlong (in category 'tests') -----
  testAtomicUlong
  
  	self
  		flag: #ffiLongVsInt;
+ 		assert: (self argTypesAt: #ffiTestUint:with:with:with:) allButFirst
- 		assert: (self argTypesAt: #ffiTestUlong:with:with:with:) allButFirst
  		equals: (Array new: 4 withAll: ExternalType ulong).!

Item was changed:
  ----- Method: FFITypeNameTests>>testStruct (in category 'tests') -----
  testStruct
  
  	self
+ 		assert: (self argTypesAt: #ffiTestStruct64:with:)
- 		assert: (self argTypesAt: #ffiTestPoint2:with:)
  		equals: (Array new: 3 withAll: FFITestPoint2 externalType).!



More information about the Squeak-dev mailing list