[squeak-dev] FFI: FFI-Kernel.terf-mt.189.mcz

commits at source.squeak.org commits at source.squeak.org
Mon Aug 9 07:44:59 UTC 2021


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

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

Name: FFI-Kernel.terf-mt.189
Author: mt
Time: 9 August 2021, 9:44:58.47481 am
UUID: 721f872c-37f0-3846-b83e-53fcd39b7734
Ancestors: FFI-Kernel.terf-eem.188

Backports the most recent bugfixes from the main branch (i.e., FFI-Kernel-mt.188) to make all tests pass again (instead of crashing the VM). The most important fix seems to be the regression in #zeroMemory: that FFI-Kernel-eem.182 introduced.

Note that the following hacks might have to be re-added if really needed for Terf:
- ExternalStructure class >> #allocate
- ExternalStructureType >> #allocate

Note that #initialize* methods on ExternalType class DO NOT migrate existing FFI installations. One MUST use #reset* instead.

Also note that this .tern branch is hopefuly only temporary. The FFI architecture continues to evolve on the main branch.

Finally, please read the commit message in FFI-Kernel-mt.187 (main branch).

=============== Diff against FFI-Kernel.terf-eem.188 ===============

Item was changed:
  ----- Method: ByteArray>>unsignedByteAt:put: (in category '*FFI-Kernel-accessing') -----
  unsignedByteAt: byteOffset put: value
  	"Same as #byteAt: but different primitive to support ExternalAddress."
+ 	<primitive: #primitiveUnsignedInt8AtPut module: #SqueakFFIPrims error: ec>
- 		
  	^ self integerAt: byteOffset put: value size: 1 signed: false!

Item was changed:
  ----- Method: ByteArray>>zeroMemory: (in category '*FFI-Kernel-accessing') -----
  zeroMemory: numBytes
  
  	| index size |
  	index := 1.
+ 	size := numBytes - 7.
- 	size := self size - 7.
  	[index <= size] whileTrue:
  		[self uint64At: index put: 0.
  		 index := index + 8].
+ 	size := size + 4. "7 - 3, i.e. numBytes - 3"
- 	size := size + 4. "7 - 3, i.e. self size - 3"
  	index <= size ifTrue:
  		[self uint32At: index put: 0.
  		 index := index + 4].
+ 	size := size + 2. "3 - 1, i.e. numBytes - 1"
- 	size := size + 2. "3 - 1, i.e. self size - 1"
  	index <= size ifTrue:
  		[self uint16At: index put: 0.
  		 index := index + 2].
+ 	size := size + 1.
+ 	index <= size ifTrue:
- 	index < size ifTrue:
  		[self uint8At: index put: 0]!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int16At: (in category 'read/write atomics') -----
+ int16At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int16At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int16At:put: (in category 'read/write atomics') -----
+ int16At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int16At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int32At: (in category 'read/write atomics') -----
+ int32At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int32At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int32At:put: (in category 'read/write atomics') -----
+ int32At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int32At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int64At: (in category 'read/write atomics') -----
+ int64At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int64At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int64At:put: (in category 'read/write atomics') -----
+ int64At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int64At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int8At: (in category 'read/write atomics') -----
+ int8At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int8At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>int8At:put: (in category 'read/write atomics') -----
+ int8At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray int8At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>perform:with: (in category 'message handling') -----
+ perform: aSymbol with: firstObject
+ 	"Needed because of AtomicSelectors. See FFIAtomicReadWriteSend >> #handle:at:."
+ 	
+ 	<primitive: 83>
+ 	^ self perform: aSymbol withArguments: { firstObject }!

Item was added:
+ ----- Method: ByteArrayReadWriter>>perform:with:with: (in category 'message handling') -----
+ perform: aSymbol with: firstObject with: secondObject
+ 	"Needed because of AtomicSelectors. See FFIAtomicReadWriteSend >> #handle:at:."
+ 	
+ 	<primitive: 83>
+ 	^ self perform: aSymbol withArguments: { firstObject. secondObject }!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint16At: (in category 'read/write atomics') -----
+ uint16At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint16At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint16At:put: (in category 'read/write atomics') -----
+ uint16At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint16At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint32At: (in category 'read/write atomics') -----
+ uint32At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint32At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint32At:put: (in category 'read/write atomics') -----
+ uint32At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint32At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint64At: (in category 'read/write atomics') -----
+ uint64At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint64At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint64At:put: (in category 'read/write atomics') -----
+ uint64At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint64At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint8At: (in category 'read/write atomics') -----
+ uint8At: oByteOffset
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint8At: oByteOffset + byteOffset!

Item was added:
+ ----- Method: ByteArrayReadWriter>>uint8At:put: (in category 'read/write atomics') -----
+ uint8At: oByteOffset put: value
+ 
+ 	self checkAt: oByteOffset.
+ 	^ byteArray uint8At: oByteOffset + byteOffset put: value!

Item was added:
+ ----- Method: ByteString>>uint8At: (in category '*FFI-Kernel-accessing') -----
+ uint8At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: ByteString>>uint8At:put: (in category '*FFI-Kernel-accessing') -----
+ uint8At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value asCharacter!

Item was added:
+ ----- Method: DoubleByteArray>>uint16At: (in category '*FFI-Kernel-accessing') -----
+ uint16At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: DoubleByteArray>>uint16At:put: (in category '*FFI-Kernel-accessing') -----
+ uint16At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was added:
+ ----- Method: DoubleWordArray>>uint64At: (in category '*FFI-Kernel-accessing') -----
+ uint64At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: DoubleWordArray>>uint64At:put: (in category '*FFI-Kernel-accessing') -----
+ uint64At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was added:
+ ----- Method: ExternalData>>atAllPut: (in category 'accessing') -----
+ atAllPut: anObject
+ 
+ 	self sizeCheck.	
+ 	1 to: self size do:
+ 		[:index | self at: index put: anObject].!

Item was changed:
  ----- Method: ExternalStructure class>>allocate (in category 'instance creation') -----
  allocate
+ 
+ 	^self externalType allocate!
- 	^ self fromHandle: (ByteArray new: self byteSize)!

Item was added:
+ ----- Method: ExternalStructure class>>cleanUp: (in category 'initialize-release') -----
+ cleanUp: aggressive
+ 
+ 	aggressive ifTrue: [externalType := nil].!

Item was removed:
- ----- Method: ExternalStructureType>>allocate (in category 'external data') -----
- allocate
- 	^ referentClass fromHandle: (ByteArray new: self byteSize)!

Item was changed:
  ----- Method: ExternalType class>>cleanupUnusedTypes (in category 'housekeeping') -----
  cleanupUnusedTypes
  	"In the lookup table for struct types and array types, remove keys to types no longer present..
  		
  	ExternalType cleanupUnusedTypes
  	"
  	Smalltalk garbageCollect.	
  	StructTypes keys do: [:key |
  		(StructTypes at: key) ifNil: [
  			StructTypes removeKey: key]].
  	
  	ArrayTypes keys do: [:contentTypeName |
  		| sizes |
  		sizes := ArrayTypes at: contentTypeName.
+ 		sizes keys do: [:size |
- 		[sizes keys do: [:size |
  			(sizes at: size) ifNil: [sizes removeKey: size]].
+ 		sizes ifEmpty: [
+ 			ArrayTypes removeKey: contentTypeName]].!
- 		 sizes ifEmpty: [
- 			ArrayTypes removeKey: contentTypeName]]
- 			on: Error
- 			do: [:ex| Transcript print: ex; cr; flush]]!

Item was changed:
  ----- Method: ExternalType class>>initializeAtomicTypes (in category 'class initialization') -----
  initializeAtomicTypes
+ 	"Initializes atomic types if not already initialized. NOTE that if you want to reset already initialized atomic types, use #resetAllAtomicTypes instead."
- 	"ExternalType initialize"
  	
  	| atomicType byteSize type typeName byteAlignment |
  	self flag: #ffiLongVsInt. "For a discussion about long vs. int see http://forum.world.st/Re-squeak-dev-64-bit-FFI-was-porting-Croquet-to-Squeak6-0-alpha-tp5113318.html."
+ 	
- 	AtomicTypes do:
- 		[:anAtomicType|
- 		(anAtomicType class ~~ ExternalAtomicType
- 		 and: [anAtomicType class == ExternalType]) ifTrue:
- 			[ExternalAtomicType adoptInstance: anAtomicType]].
  	#(
  		"name		atomic id		byte size	byte alignment"
  		('void' 		0 				0			0) "No non-pointer support in calls. Duh. ;-)"
  		('bool' 		1 				1			1) "No pointer support in calls."
  		('byte' 		2 				1			1)
  		('sbyte' 	3 				1			1)
  		('ushort' 	4 				2			2)
  		('short' 		5 				2			2)
  "!!!!!!"	('ulong' 	6 				4 "!!!!!!"		4)
  "!!!!!!"	('long' 		7 				4 "!!!!!!"		4)
  		('ulonglong' 8 				8			8) "v.i."
  		('longlong' 	9 				8			8) "v.i."
  		('char' 		10 				1			1)
  		('schar' 	11 				1			1)
  		('float' 		12 				4			4)
  		('double' 	13 				8			8) "v.i."
  "TODO: ('longdouble' 14			10			16? 4?)"
  	) do:[:typeSpec| | compiled |
  		typeName := typeSpec first.
  		atomicType := typeSpec second.
  		byteSize := typeSpec third.
  		byteAlignment := typeSpec fourth.
  		
  		"0) On 32-bits Windows and MacOS, double and long long have an alignment of 8. But on 32-bit Linux, their alignment is 4. But not on a 32-bit Raspberry Pi OS."
  		(FFIPlatformDescription current wordSize = 4
  			and: [FFIPlatformDescription current isUnix
  			and: [FFIPlatformDescription current isARM not]]) ifTrue: [
  				(#('double' 'longlong' 'ulonglong') includes: typeName) ifTrue: [
  					byteAlignment := 4]].
  		
  		"1) Regular type"
  		type := (AtomicTypes at: typeName).
  		compiled := WordArray with: ((byteSize bitOr: FFIFlagAtomic) bitOr:
  				(atomicType bitShift: FFIAtomicTypeShift)).
  		compiled ~= type compiledSpec
  			"Preserve the identity of #compiledSpec."
  			ifTrue: [type compiledSpec: compiled].
  		type byteAlignment: byteAlignment.
  		
  		"2) Pointer type"
  		type := type asPointerType.
  		compiled := WordArray with: ((self pointerSpec bitOr: FFIFlagAtomic) bitOr:
  				(atomicType bitShift: FFIAtomicTypeShift)).
  		compiled ~= type compiledSpec
  			"Preserve the identity of #compiledSpec."
  			ifTrue: [type compiledSpec: compiled].
  		type byteAlignment: self pointerAlignment.
  	].!

Item was changed:
  ----- Method: ExternalType class>>resetAllAtomicTypes (in category 'housekeeping') -----
  resetAllAtomicTypes
  	"Warning: This call is only required if you change the initialization for AtomicTypes."
  
  	AtomicTypes := nil.
  	AtomicSends := nil.
  	ArrayClasses := nil.
  	
+ 	StructTypes := nil. ExternalStructure withAllSubclassesDo: [:cls | cls cleanUp: true].
- 	StructTypes := nil.
  	ArrayTypes := nil.
  	
  	self initializeDefaultTypes.
  	self initializeArrayClasses.
  	self resetAllStructureTypes.!

Item was changed:
  ----- Method: ExternalType class>>resetAllStructureTypes (in category 'housekeeping') -----
  resetAllStructureTypes
  	"Warning: This call is only required if you change the container for StructTypes!! Note that (2) and (3) can be swapped but that puts unnecessary pressure on the GC."
  
+ 	StructTypes := nil. ExternalStructure withAllSubclassesDo: [:cls | cls cleanUp: true].
- 	StructTypes := nil.
  	ArrayTypes := nil.
  	
  	"1) Initialize the container for structure types."
  	self initializeStructureTypes.
  		
  	"2) Recompile all FFI calls to create and persist structure types."
  	self recompileAllLibraryFunctions.
  	
  	"3) Update all structure types' spec and alignment."
  	ExternalTypePool reset.
  	ExternalStructure defineAllFields.
  	ExternalTypePool cleanUp.
  !

Item was changed:
  ----- Method: ExternalType class>>typeNamed: (in category 'instance lookup') -----
  typeNamed: typeName
  	"Supports pointer-type lookup for both atomic and structure types.
  	Examples: 'long', 'long*', 'long *' or 'MyStruct', 'MyStruct*', 'MyStruct *', 'IntPtr', '*IntPtr' "
  	
  	| isPointerType isNonPointerType isArrayType actualTypeName type |
+ 	isArrayType := false. isNonPointerType := false.
  	actualTypeName := typeName copyWithoutAll: ' '.
  
  	(isPointerType := actualTypeName last == $*) "e.g. MyStruct*"
  		ifTrue: [actualTypeName := actualTypeName allButLast].
  	actualTypeName last == $) "e.g. (char[])* -- pointer type for array type"
  		ifTrue: [actualTypeName := (actualTypeName copyFrom: 2 to: actualTypeName size - 1)].
  	(isNonPointerType := actualTypeName first == $*) "e.g. *DoublePtr"
  		ifTrue: [actualTypeName := actualTypeName allButFirst].
  
  	(isArrayType := actualTypeName last == $])
  		ifTrue: [ type := self arrayTypeNamed: actualTypeName ]
  		ifFalse: [
  			(Symbol lookup: actualTypeName)
  				ifNotNil: [:sym | actualTypeName := sym].
  			type := (self atomicTypeNamed: actualTypeName)
  				ifNil: [self structTypeNamed: actualTypeName]].
  
+ 	^ type ifNotNil: [
+ 		isPointerType
- 	^ type ifNotNil:
- 		[isPointerType
  			ifTrue: [type asPointerType "e.g. int* MyStruct* "]
  			ifFalse: [isNonPointerType
  				ifTrue: [type asNonPointerType "e.g. *IntPtr *MyStructPtr "]
  				ifFalse: [type "e.g. int IntPtr MyStruct MyStructPtr "]]]!

Item was changed:
  ----- Method: ExternalType>>isTypeAlias (in category 'testing') -----
  isTypeAlias
  	
+ 	self subclassResponsibility.!
- 	^true ifTrue: [false] ifFalse: [self subclassResponsibility]!

Item was removed:
- ----- Method: ExternalUnknownType>>readFieldAt: (in category 'external structure') -----
- readFieldAt: anInteger
- 	^'self error: ''cannot read field at ', anInteger printString, '; field has unknown type'''!

Item was removed:
- ----- Method: ExternalUnknownType>>writeFieldAt:with: (in category 'external structure') -----
- writeFieldAt: anInteger with: aString
- 	^'self error: ''cannot read field at ', anInteger printString, ' with name ', aString, '; field has unknown type'''!

Item was added:
+ ----- Method: Float32Array>>floatAt: (in category '*FFI-Kernel-accessing') -----
+ floatAt: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 	
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: Float32Array>>floatAt:put: (in category '*FFI-Kernel-accessing') -----
+ floatAt: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:put:."
+ 	
+ 	^ self atByteOffset: byteOffset put: value!

Item was added:
+ ----- Method: Float64Array>>doubleAt: (in category '*FFI-Kernel-accessing') -----
+ doubleAt: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: Float64Array>>doubleAt:put: (in category '*FFI-Kernel-accessing') -----
+ doubleAt: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:put:."
+ 	
+ 	^ self atByteOffset: byteOffset put: value!

Item was changed:
  ----- Method: IntegerReadWriteSend>>isReading (in category 'accessing') -----
  isReading
  
+ 	^ selector numArgs = 3 or: [selector numArgs = 1]!
- 	^ selector numArgs = 3!

Item was added:
+ ----- Method: SignedByteArray>>int8At: (in category '*FFI-Kernel-accessing') -----
+ int8At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: SignedByteArray>>int8At:put: (in category '*FFI-Kernel-accessing') -----
+ int8At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was added:
+ ----- Method: SignedDoubleByteArray>>int16At: (in category '*FFI-Kernel-accessing') -----
+ int16At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: SignedDoubleByteArray>>int16At:put: (in category '*FFI-Kernel-accessing') -----
+ int16At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was added:
+ ----- Method: SignedDoubleWordArray>>int64At: (in category '*FFI-Kernel-accessing') -----
+ int64At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: SignedDoubleWordArray>>int64At:put: (in category '*FFI-Kernel-accessing') -----
+ int64At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was added:
+ ----- Method: SignedWordArray>>int32At: (in category '*FFI-Kernel-accessing') -----
+ int32At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: SignedWordArray>>int32At:put: (in category '*FFI-Kernel-accessing') -----
+ int32At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was added:
+ ----- Method: WordArray>>uint32At: (in category '*FFI-Kernel-accessing') -----
+ uint32At: byteOffset
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset!

Item was added:
+ ----- Method: WordArray>>uint32At:put: (in category '*FFI-Kernel-accessing') -----
+ uint32At: byteOffset put: value
+ 	"Backstop for compatibility with handle-based access. Raw-bits arrays are their own handle. See #getHandle and ExternalType >> #handle:at:."
+ 
+ 	^ self atByteOffset: byteOffset put: value!

Item was changed:
  (PackageInfo named: 'FFI-Kernel') postscript: '"Reinitialize FFIAtomicReadWriteSend to use the new accessors"
+ ExternalType resetAllAtomicTypes.'!
- ExternalType initializeDefaultTypes'!



More information about the Squeak-dev mailing list