[Vm-dev] VM Maker: VMMaker.oscog-nice.2749.mcz

commits at source.squeak.org commits at source.squeak.org
Fri May 1 21:22:33 UTC 2020


Nicolas Cellier uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-nice.2749.mcz

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

Name: VMMaker.oscog-nice.2749
Author: nice
Time: 1 May 2020, 11:21:23.890426 pm
UUID: 8c7cd18f-0bad-3b48-aa61-005ac6d4732d
Ancestors: VMMaker.oscog-eem.2748

Introduce Float64ArrayPlugin which is same as FloatArrayPlugin but for Float64Array.
This can work in Spur which provides DoubleWordArray.

This requires one VM function which where not in API: isLong64s().
Thus it will require a new platforms/Cross/vm/sqVirtualMachine.[ch] definition of interpreter proxy.
While at it, also add isShorts() to the API.
Hence increment the VM_PROXY_MINOR.

Introduce a new primitiveFromFloat64Array to FloatArrayPlugin to initialize a FloatArray from a Float64Array.
This is required for example for Smallapack when coercing single<->double precision.
If this plugin is regenerated, then platforms/Cross/vm/sqVirtualMachine.[ch] must be upgraded accordingly.

=============== Diff against VMMaker.oscog-eem.2748 ===============

Item was added:
+ InterpreterPlugin subclass: #Float64ArrayPlugin
+ 	instanceVariableNames: ''
+ 	classVariableNames: ''
+ 	poolDictionaries: ''
+ 	category: 'VMMaker-Plugins'!
+ 
+ !Float64ArrayPlugin commentStamp: 'tpr 5/2/2003 15:42' prior: 0!
+ Float64ArrayPlugin provides fast access to Float64Arrays for batch processing of double precision Float numbers!

Item was added:
+ ----- Method: Float64ArrayPlugin class>>declareCVarsIn: (in category 'translation to C') -----
+ declareCVarsIn: cg
+ 	"Nothing to declare..."!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveAddFloat64Array (in category 'arithmetic primitives') -----
+ primitiveAddFloat64Array
+ 	"Primitive. Add the receiver and the argument, both Float64Arrays and store the result into the receiver."
+ 	| rcvr arg rcvrPtr argPtr length |
+ 	<export: true>
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #argPtr type: #'double *'>
+ 	arg := interpreterProxy stackValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	((interpreterProxy isLong64s: arg)
+ 	 and: [(interpreterProxy isLong64s: rcvr)
+ 	 and: [(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr)]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (rcvrPtr at: i) + (argPtr at: i)].
+ 	interpreterProxy pop: 1. "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveAddScalar (in category 'arithmetic primitives') -----
+ primitiveAddScalar
+ 	"Primitive. Add the argument, a scalar value to the receiver, a Float64Array"
+ 	| rcvr rcvrPtr value length |
+ 	<export: true>
+ 	<var: #value type: #double>
+ 	<var: #rcvrPtr type:#'double *'>
+ 	value := interpreterProxy stackFloatValue: 0.
+ 	interpreterProxy failed ifTrue:[^nil].
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	(interpreterProxy isLong64s: rcvr) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	length := interpreterProxy stSizeOf: rcvr.
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (rcvrPtr at: i) + value].
+ 	interpreterProxy pop: 1. "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveAt (in category 'access primitives') -----
+ primitiveAt
+ 	<export: true>
+ 	| index rcvr doublePtr |
+ 	<var: #doublePtr type: #'double *'>
+ 	index := interpreterProxy stackIntegerValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	(interpreterProxy failed not
+ 	 and: [(interpreterProxy isLong64s: rcvr)
+ 	 and: [index > 0 and: [index <= (interpreterProxy slotSizeOf: rcvr)]]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	doublePtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	interpreterProxy methodReturnFloat: (doublePtr at: index - 1)!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveAtPut (in category 'access primitives') -----
+ primitiveAtPut
+ 
+ 	| value floatValue index rcvr doublePtr |
+ 	<export: true>
+ 	<var: #floatValue type: #double>
+ 	<var: #doublePtr type: #'double *'>
+ 	value := interpreterProxy stackValue: 0.
+ 	floatValue := (interpreterProxy isIntegerObject: value)
+ 					ifTrue: [(interpreterProxy integerValueOf: value) asFloat]
+ 					ifFalse: [interpreterProxy floatValueOf: value].
+ 	index := interpreterProxy stackIntegerValue: 1.
+ 	rcvr := interpreterProxy stackValue: 2.
+ 	(interpreterProxy failed not
+ 	 and: [(interpreterProxy isLong64s: rcvr)
+ 	 and: [index > 0 and: [index <= (interpreterProxy slotSizeOf: rcvr)]]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	doublePtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	doublePtr at: index-1 put: floatValue.
+ 	interpreterProxy pop: 3 thenPush: value!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveDivFloat64Array (in category 'arithmetic primitives') -----
+ primitiveDivFloat64Array
+ 	"Primitive. Divide each element in the receiver by the corresponding element in the argument, both Float64Arrays, and store the result into the receiver."
+ 	<export: true>
+ 	| rcvr arg rcvrPtr argPtr length |
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #argPtr type: #'double *'>
+ 	arg := interpreterProxy stackValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	((interpreterProxy isLong64s: arg)
+ 	 and: [(interpreterProxy isLong64s: rcvr)
+ 	 and: [(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr)]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'double *'.
+ 	"Check if any of the argument's values is zero"
+ 	0 to: length - 1 do:
+ 		[:i| (argPtr at: i) = 0.0 ifTrue: "i.e. check for both 0.0 and -0.0"
+ 			[^interpreterProxy primitiveFail]].
+ 	0 to: length - 1 do:
+ 		[:i| rcvrPtr at: i put: (rcvrPtr at: i) / (argPtr at: i)].
+ 	interpreterProxy pop: 1 "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveDivScalar (in category 'arithmetic primitives') -----
+ primitiveDivScalar
+ 	"Primitive. Divide each element in the receiver by the argument, a scalar, and store the result into the receiver, a Float64Array"
+ 	| rcvr rcvrPtr value length |
+ 	<export: true>
+ 	<var: #value type: #double>
+ 	<var: #rcvrPtr type:#'double *'>
+ 	value := interpreterProxy stackFloatValue: 0.
+ 	interpreterProxy failed ifTrue:[^nil].
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	(interpreterProxy isLong64s: rcvr) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	length := interpreterProxy stSizeOf: rcvr.
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (rcvrPtr at: i) / value.
+ 	].
+ 	interpreterProxy pop: 1 "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveDotProduct (in category 'arithmetic primitives') -----
+ primitiveDotProduct
+ 	"Primitive. Compute the dot product of the receiver and the argument, both Float64Arrays.
+ 	The dot product is defined as the sum of the products of the individual elements."
+ 	<export: true>
+ 	| rcvr arg rcvrPtr argPtr length result |
+ 	<var: #result type: #double>
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #argPtr type: #'double *'>
+ 	arg := interpreterProxy stackValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	((interpreterProxy isLong64s: arg)
+ 	 and: [(interpreterProxy isLong64s: rcvr)
+ 	 and: [(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr)]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'double *'.
+ 	result := 0.0.
+ 	0 to: length-1 do:[:i|
+ 		result := result + ((rcvrPtr at: i) * (argPtr at: i)).
+ 	].
+ 	interpreterProxy methodReturnFloat: result. "Return result"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveEqual (in category 'access primitives') -----
+ primitiveEqual
+ 
+ 	| rcvr arg rcvrPtr argPtr length |
+ 	<export: true>
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #argPtr type: #'double *'>
+ 	arg := interpreterProxy stackValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	((interpreterProxy isLong64s: arg)
+ 	 and: [(interpreterProxy isLong64s: rcvr)]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	interpreterProxy pop: 2.
+ 	(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr) ifFalse:
+ 		[^interpreterProxy pushBool: false].
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		(rcvrPtr at: i) = (argPtr at: i) ifFalse:[^interpreterProxy pushBool: false].
+ 	].
+ 	^interpreterProxy pushBool: true!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveFromFloatArray (in category 'access primitives') -----
+ primitiveFromFloatArray
+ 	"Primitive. Set each element of the receiver, a Float64Array with that of the argument, a FloatArray and return the receiver.
+ 	Fail if both have different size"
+ 	| rcvr arg rcvrPtr argPtr length |
+ 	<export: true>
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #argPtr type: #'float *'>
+ 	arg := interpreterProxy stackValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	((interpreterProxy isWords: arg)
+ 	 and: [(interpreterProxy isLong64s: rcvr)
+ 	 and: [(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr)]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'float *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (self cCoerce: (argPtr at: i) to: #double)].
+ 	interpreterProxy pop: 1. "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveHashArray (in category 'access primitives') -----
+ primitiveHashArray
+ 
+ 	| rcvr rcvrPtr length result |
+ 	<export: true>
+ 	<var: #rcvrPtr type: #'unsigned int *'>
+ 	<var: #result type: #'unsigned int'>
+ 	rcvr := interpreterProxy stackValue: 0.
+ 	(interpreterProxy isLong64s: rcvr) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	length := interpreterProxy stSizeOf: rcvr.
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'unsigned int *'.
+ 	result := 0.
+ 	0 to: length*2-1 do:[:i|
+ 		result := result + (rcvrPtr at: i).
+ 	].
+ 	interpreterProxy methodReturnInteger: (result bitAnd: 16r1FFFFFFF)!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveLength (in category 'arithmetic primitives') -----
+ primitiveLength
+ 	"Primitive. Compute the length of the argument (sqrt of sum of component squares)."
+ 	<export: true>
+ 	| rcvr rcvrPtr length len |
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #len type: #double>
+ 	rcvr := interpreterProxy stackValue: 0.
+ 	(interpreterProxy isLong64s: rcvr) ifFalse:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	length := interpreterProxy stSizeOf: rcvr.
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	len := 0.0.
+ 	0 to: length-1 do:
+ 		[:i| len := len + ((rcvrPtr at: i) * (rcvrPtr at: i)) ].
+ 	len > 0.0 ifFalse:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	interpreterProxy methodReturnFloat: (self sqrt: len)!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveMulFloat64Array (in category 'arithmetic primitives') -----
+ primitiveMulFloat64Array
+ 	"Primitive. Multiply the receiver and the argument, both Float64Arrays and store the result into the receiver."
+ 	<export: true>
+ 	| rcvr arg rcvrPtr argPtr length |
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #argPtr type: #'double *'>
+ 	arg := interpreterProxy stackValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	((interpreterProxy isLong64s: arg)
+ 	 and: [(interpreterProxy isLong64s: rcvr)
+ 	 and: [(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr)]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (rcvrPtr at: i) * (argPtr at: i).
+ 	].
+ 	interpreterProxy pop: 1 "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveMulScalar (in category 'arithmetic primitives') -----
+ primitiveMulScalar
+ 	<export: true>
+ 	"Primitive. Multiply elements in the receiver, a Float64Array, by argument, a scalar value, and store the result into the receiver."
+ 	| rcvr rcvrPtr value length |
+ 	<var: #value type: #double>
+ 	<var: #rcvrPtr type:#'double *'>
+ 	value := interpreterProxy stackFloatValue: 0.
+ 	interpreterProxy failed ifTrue:[^nil].
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	(interpreterProxy isLong64s: rcvr) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	length := interpreterProxy stSizeOf: rcvr.
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (rcvrPtr at: i) * value.
+ 	].
+ 	interpreterProxy pop: 1 "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveNormalize (in category 'arithmetic primitives') -----
+ primitiveNormalize
+ 	"Primitive. Normalize the argument (A Float64Array) in place."
+ 	<export: true>
+ 	| rcvr rcvrPtr length len |
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #len type: #double>
+ 	rcvr := interpreterProxy stackValue: 0.
+ 	(interpreterProxy isLong64s: rcvr) ifFalse:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	length := interpreterProxy stSizeOf: rcvr.
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	len := 0.0.
+ 	0 to: length - 1 do:
+ 		[:i| len := len + ((rcvrPtr at: i) * (rcvrPtr at: i)) ].
+ 	len > 0.0 ifFalse:
+ 		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 
+ 	len := self sqrt: len.
+ 	0 to: length - 1 do:
+ 		[:i| rcvrPtr at: i put: (rcvrPtr at: i) / len ].
+ 
+ 	"Leave receiver on the stack."!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveSubFloat64Array (in category 'arithmetic primitives') -----
+ primitiveSubFloat64Array
+ 	"Primitive. Subtract each element in the argument from each element in the receiver, both Float64Arrays and store the result into the receiver."
+ 	<export: true>
+ 	| rcvr arg rcvrPtr argPtr length |
+ 	<var: #rcvrPtr type: #'double *'>
+ 	<var: #argPtr type: #'double *'>
+ 	arg := interpreterProxy stackValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	((interpreterProxy isLong64s: arg)
+ 	 and: [(interpreterProxy isLong64s: rcvr)
+ 	 and: [(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr)]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (rcvrPtr at: i) - (argPtr at: i).
+ 	].
+ 	interpreterProxy pop: 1 "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveSubScalar (in category 'arithmetic primitives') -----
+ primitiveSubScalar
+ 	"Primitive. Subtract the argument, a scalar value from  each element in the receiver, a Float64Array"
+ 	<export: true>
+ 	| rcvr rcvrPtr value length |
+ 	<var: #value type: #double>
+ 	<var: #rcvrPtr type:#'double *'>
+ 	value := interpreterProxy stackFloatValue: 0.
+ 	interpreterProxy failed ifTrue:[^nil].
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	(interpreterProxy isLong64s: rcvr) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	length := interpreterProxy stSizeOf: rcvr.
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (rcvrPtr at: i) - value.
+ 	].
+ 	interpreterProxy pop: 1 "Leave rcvr on stack"!

Item was added:
+ ----- Method: Float64ArrayPlugin>>primitiveSum (in category 'arithmetic primitives') -----
+ primitiveSum
+ 	"Primitive. Answer the sum of each float in the receiver, a Float64Array."
+ 	<export: true>
+ 	| rcvr rcvrPtr length sum |
+ 	<var: #sum type: #double>
+ 	<var: #rcvrPtr type: #'double *'>
+ 	rcvr := interpreterProxy stackValue: 0.
+ 	(interpreterProxy isLong64s: rcvr) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	length := interpreterProxy stSizeOf: rcvr.
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'double *'.
+ 	sum := 0.0.
+ 	0 to: length-1 do:[:i|
+ 		sum := sum + (rcvrPtr at: i).
+ 	].
+ 	interpreterProxy methodReturnFloat: sum!

Item was added:
+ ----- Method: Float64ArrayPlugin>>sqrt: (in category 'simulation') -----
+ sqrt: aFloat
+ 	<doNotGenerate>
+ 	^aFloat sqrt!

Item was added:
+ ----- Method: FloatArrayPlugin>>primitiveFromFloat64Array (in category 'access primitives') -----
+ primitiveFromFloat64Array
+ 	"Primitive. Set each element of the receiver, a FloatArray with that of the argument, a Float64Array and return the receiver.
+ 	Note that this conversion might loose bits, or generate overflow.
+ 	Fail if both have different size"
+ 	| rcvr arg rcvrPtr argPtr length |
+ 	<export: true>
+ 	<option: #SPURVM>
+ 	<var: #rcvrPtr type: #'float *'>
+ 	<var: #argPtr type: #'double *'>
+ 	arg := interpreterProxy stackValue: 0.
+ 	rcvr := interpreterProxy stackValue: 1.
+ 	((interpreterProxy isLong64s: arg)
+ 	 and: [(interpreterProxy isWords: rcvr)
+ 	 and: [(length := interpreterProxy stSizeOf: arg) = (interpreterProxy stSizeOf: rcvr)]]) ifFalse:
+ 		[^interpreterProxy primitiveFail].
+ 	rcvrPtr := self cCoerce: (interpreterProxy firstIndexableField: rcvr) to: #'float *'.
+ 	argPtr := self cCoerce: (interpreterProxy firstIndexableField: arg) to: #'double *'.
+ 	0 to: length-1 do:[:i|
+ 		rcvrPtr at: i put: (self cCoerce: (argPtr at: i) to: #float)].
+ 	interpreterProxy pop: 1. "Leave rcvr on stack"!

Item was changed:
  ----- Method: SpurMemoryManager class>>vmProxyMinorVersion (in category 'api characterization') -----
  vmProxyMinorVersion
+ 	"Define the  VM_PROXY_MINOR version for this VM as used to define
- 	"Define the  VM_PROXY_MAJOR version for this VM as used to define
  	 the api in platforms/Cross/vm/sqVirtualMachine.[ch] and in interp.h."
+ 	^17 "isShorts isLong64s"!
- 	^16 "classDoubleByteArray classWordArray classDoubleWordArray classFloat32Array classFloat64Array"!

Item was changed:
  ----- Method: SpurMemoryManager>>isLong64s: (in category 'object testing') -----
  isLong64s: oop
  	"Answer if the argument contains only indexable 64-bit double words (no oops). See comment in formatOf:"
  
+ 	<api>
  	^(self isNonImmediate: oop)
  	  and: [self isLong64sNonImm: oop]!

Item was changed:
  ----- Method: SpurMemoryManager>>isShorts: (in category 'object testing') -----
  isShorts: oop
  	"Answer if the argument contains only indexable 16-bit half words (no oops). See comment in formatOf:"
  
+ 	<api>
  	^(self isNonImmediate: oop)
  	  and: [self isShortsNonImm: oop]!

Item was changed:
  ----- Method: VMMaker class>>generateVMPlugins (in category 'configurations') -----
  generateVMPlugins
  	^VMMaker
  		generatePluginsTo: self sourceTree, '/src'
  		options: #()
  		platformDir: self sourceTree, '/platforms'
  		including:#(ADPCMCodecPlugin AsynchFilePlugin
  					BalloonEnginePlugin B3DAcceleratorPlugin B3DEnginePlugin BMPReadWriterPlugin BitBltSimulation
  					BochsIA32Plugin BochsX64Plugin GdbARMv6Plugin GdbARMv8Plugin
  					CameraPlugin CroquetPlugin DeflatePlugin DropPlugin
  					"Cryptography Plugins:" DESPlugin DSAPlugin MD5Plugin SHA256Plugin
+ 					"FT2Plugin" FFTPlugin FileCopyPlugin FilePlugin FileAttributesPlugin Float64ArrayPlugin FloatArrayPlugin FloatMathPlugin
- 					"FT2Plugin" FFTPlugin FileCopyPlugin FilePlugin FileAttributesPlugin FloatArrayPlugin FloatMathPlugin
  					GeniePlugin HostWindowPlugin IA32ABIPlugin ImmX11Plugin InternetConfigPlugin
  					JPEGReadWriter2Plugin JPEGReaderPlugin JoystickTabletPlugin KlattSynthesizerPlugin
  					LargeIntegersPlugin LocalePlugin MIDIPlugin MacMenubarPlugin Matrix2x3Plugin
  					MiscPrimitivePlugin Mpeg3Plugin QuicktimePlugin RePlugin
  					ScratchPlugin SecurityPlugin SerialPlugin SocketPlugin
  					SoundCodecPlugin SoundGenerationPlugin SoundPlugin SqueakSSLPlugin StarSqueakPlugin
  					ThreadedFFIPlugin ThreadedARM32FFIPlugin ThreadedARM64FFIPlugin ThreadedIA32FFIPlugin
  					ThreadedX64SysVFFIPlugin ThreadedX64Win64FFIPlugin
  					UnicodePlugin UnixAioPlugin UUIDPlugin UnixOSProcessPlugin
  					Win32OSProcessPlugin VMProfileLinuxSupportPlugin VMProfileMacSupportPlugin WeDoPlugin
  					XDisplayControlPlugin)!



More information about the Vm-dev mailing list