[Vm-dev] VM Maker: VMMaker.oscog-eem.948.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Nov 21 02:39:45 UTC 2014


Eliot Miranda uploaded a new version of VMMaker to project VM Maker:
http://source.squeak.org/VMMaker/VMMaker.oscog-eem.948.mcz

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

Name: VMMaker.oscog-eem.948
Author: eem
Time: 20 November 2014, 6:37:08.579 pm
UUID: 9323b2ad-f5cf-4aca-8f31-67eb5616ccca
Ancestors: VMMaker.oscog-eem.947

Spur:
Fix regression in primitiveNewWithArg from
VMMaker.oscog-eem.859 which caused basicNew:
on fixed classes to raise OutOfMemory instead of
the relevant error.

Slang:
Fix FilePluginSimulator>>fileValueOf: given
VMMaker.oscog-eem.946's sizeof: changes.

Use isFloat instead of class == Float in anticipation
of SmallFloat.

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

Item was changed:
  ----- Method: FilePluginSimulator>>fileValueOf: (in category 'simulation') -----
  fileValueOf: objectPointer
  	| index file |
  	index := (interpreterProxy isIntegerObject: objectPointer)
  				ifTrue: [interpreterProxy integerValueOf: objectPointer]
  				ifFalse:
  					[((interpreterProxy isBytes: objectPointer)
+ 					  and: [(interpreterProxy byteSizeOf: objectPointer) = (self sizeof: #SQFile)]) ifFalse:
- 					  and: [(interpreterProxy byteSizeOf: objectPointer) = interpreterProxy wordSize]) ifFalse:
  						[interpreterProxy primitiveFail.
  						 ^nil].
  					interpreterProxy longAt: objectPointer + interpreterProxy baseHeaderSize].
  	file := openFiles at: index.
  	"this attempts to preserve file positions across snapshots when debugging the VM
  	 requires saving an image in full flight and pushing it over the cliff time after time..."
  	(file closed and: [states includesKey: file]) ifTrue:
  		[[:pos :isBinary|
  		  file reopen; position: pos.
  		  isBinary ifTrue:
  			[file binary]] valueWithArguments: (states at: file)].
  	^file!

Item was changed:
  ----- Method: InterpreterPrimitives>>primitiveNewWithArg (in category 'object access primitives') -----
  primitiveNewWithArg
  	"Allocate a new indexable instance. Fail if the allocation would leave less than lowSpaceThreshold bytes free. May cause a GC."
+ 	| size spaceOkay instSpec |
- 	| size spaceOkay |
  	size := self positiveMachineIntegerValueOf: self stackTop.
  	self cppIf: NewspeakVM
  		ifTrue: "For the mirror prims check that the class obj is actually a valid class."
  			[(argumentCount < 2
  			  or: [self addressCouldBeClassObj: (self stackValue: 1)]) ifFalse:
  				[self primitiveFailFor: PrimErrBadArgument]].
  	self successful "positiveMachineIntegerValueOf: succeeds only for non-negative integers."
  		ifTrue:
  			[objectMemory hasSpurMemoryManagerAPI
  				ifTrue:
  					[(objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)
  						ifNotNil: [:obj| self pop: argumentCount + 1 thenPush: obj]
+ 						ifNil: [instSpec := objectMemory instSpecOfClass: (self stackValue: 1).
+ 							  self primitiveFailFor: (((objectMemory isIndexableFormat: instSpec)
+ 													and: [(objectMemory isCompiledMethodFormat: instSpec) not])
+ 														ifTrue: [PrimErrNoMemory]
+ 														ifFalse: [PrimErrBadReceiver])]]
- 						ifNil: [self primitiveFailFor: ((objectMemory isCompiledMethodFormat: (objectMemory instSpecOfClass: (self stackValue: 1)))
- 														ifTrue: [PrimErrBadReceiver]
- 														ifFalse: [PrimErrNoMemory])]]
  				ifFalse:
  					[spaceOkay := objectMemory sufficientSpaceToInstantiate: (self stackValue: 1) indexableSize: size.
  					 spaceOkay
  						ifTrue:
  							[self
  								pop: argumentCount + 1
  								thenPush: (objectMemory instantiateClass: (self stackValue: 1) indexableSize: size)]
  						ifFalse:
  							[self primitiveFailFor: PrimErrNoMemory]]]
  		ifFalse:
  			[self primitiveFailFor: PrimErrBadArgument]!

Item was changed:
  ----- Method: InterpreterProxy>>floatObjectOf: (in category 'converting') -----
  floatObjectOf: aFloat
  	<returnTypeC: #sqInt> "...because answering the float argument causes the type inferencer to say this answers a float."
  	<var: #aFloat type: 'double '>
+ 	aFloat isFloat ifFalse:[self error:'Not a float object'].
- 	aFloat class == Float ifFalse:[self error:'Not a float object'].
  	^aFloat!

Item was changed:
  ----- Method: InterpreterProxy>>floatValueOf: (in category 'converting') -----
  floatValueOf: oop
  	<returnTypeC:'double'>
+ 	oop isFloat
- 	oop class == Float
  		ifTrue:[^oop]
  		ifFalse:[self primitiveFail. ^0.0].!

Item was changed:
  ----- Method: InterpreterProxy>>isFloatObject: (in category 'testing') -----
  isFloatObject: oop
+ 	^oop isFloat!
- 	^oop class == Float!

Item was changed:
  ----- Method: InterpreterProxy>>pushFloat: (in category 'stack access') -----
  pushFloat: f
  	<var: #f type: 'double '>
+ 	f isFloat ifFalse:[^self error:'Not a Float'].
- 	f class == Float ifFalse:[^self error:'Not a Float'].
  	self push: f.!

Item was changed:
  ----- Method: Spur64BitMemoryManager class>>isImmediate: (in category 'simulation only') -----
  isImmediate: anObject
  	self flag: 'The float range is close but probably wrong. Revisit when immediate floats are implemented'.
+ 	^(anObject isInteger and: [anObject between: self minSmallInteger and: self maxSmallInteger])
+ 	  or: [anObject isCharacter
+ 	  or: [anObject isFloat and: [anObject exponent between: -126 and: 127]]]
+ 
+ 	"1.0e-38 exponent -127
+ 	 1.0e38 exponent 126
+ 
+ 	 NumberParser new makeFloatFromMantissa: 1 exponent: 127 base: 2 1.7014118346046923e38
+ 	 (NumberParser new makeFloatFromMantissa: 1 exponent: 127 base: 2) exponent 127
+ 	 NumberParser new makeFloatFromMantissa: 1 exponent: -126 base: 2 1.1754943508222875e-38
+ 	 (NumberParser new makeFloatFromMantissa: 1 exponent: -126 base: 2) exponent -126"!
- 	^anObject class == SmallInteger
- 	  or: [anObject class == Character
- 	  or: [anObject class == Float and: [anObject exponent between: -128 and: 127]]]!



More information about the Vm-dev mailing list