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

commits at source.squeak.org commits at source.squeak.org
Wed Jun 7 21:58:22 UTC 2017


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

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

Name: VMMaker.oscog-eem.2236
Author: eem
Time: 7 June 2017, 2:57:18.014718 pm
UUID: ddbf0087-58d9-4b7a-847e-b80252e68b52
Ancestors: VMMaker.oscog-eem.2235

StackInterpreter:
Fix some simulation and initialization issues.  make sure to send str:cmp: et al to interpreterProxy (which is an object memory during simulation) to avoid the deprecation warning on byteAt:.

Make sure BytecodeSetHasExtensions is initialized in the negative for SqueakV3.

Make sure initializationOptions is initialzatied before using compactorClass in SpurMemoryManager class.

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

Item was changed:
  ----- Method: FilePluginSimulator>>fileOpenName:size:write:secure: (in category 'file primitives') -----
  fileOpenName: nameIndex size: nameSize write: writeFlag secure: secureFlag
  	"Open the named file, possibly checking security. Answer the file oop."
  	| path f index |
  	openFiles size >= maxOpenFiles ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrLimitExceeded].
+ 	path := interpreterProxy asString: nameIndex size: nameSize.
- 	path := interpreterProxy interpreter asString: nameIndex size: nameSize.
  	f := writeFlag
  			ifTrue: [FileStream fileNamed: path]
  			ifFalse:
  				[(StandardFileStream isAFileNamed: path) ifTrue:
  					[FileStream readOnlyFileNamed: path]].
  	f ifNil: [^interpreterProxy primitiveFail].
  	f binary.
  	index := openFiles size + 1.
  	openFiles at: index put: f.
  	^interpreterProxy integerObjectOf: index!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:Read:Into:At: (in category 'simulation') -----
  sqFile: file Read: count Into: byteArrayIndexArg At: startIndex
+ 	| byteArrayIndex |
- 	| interpreter byteArrayIndex |
- 	interpreter := interpreterProxy interpreter.
  	byteArrayIndex := byteArrayIndexArg asInteger. "Coerces CArray et al correctly"
  	[[startIndex to: startIndex + count - 1 do:
  		[ :i |
  		file atEnd ifTrue:
  			[(file isKindOf: FakeStdinStream) ifTrue: [file atEnd: false].
  			 ^i - startIndex].
+ 		interpreterProxy
- 		interpreter
  			byteAt: byteArrayIndex + i
  			put: (file next ifNil: [(file isKindOf: FakeStdinStream) ifTrue: [^0]] ifNotNil: [:c| c asInteger])]]
  			on: Error
  			do: [:ex|
  				(file isKindOf: TranscriptStream) ifFalse: [ex pass].
  				^0]]
  		ensure: [self recordStateOf: file].
  	^count!

Item was changed:
  ----- Method: FilePluginSimulator>>sqFile:Write:From:At: (in category 'simulation') -----
  sqFile: file Write: count From: byteArrayIndexArg At: startIndex
+ 	| byteArrayIndex |
- 	| interpreter byteArrayIndex |
- 	interpreter := interpreterProxy interpreter.
  	byteArrayIndex := byteArrayIndexArg asInteger. "Coerces CArray et al correctly"
  	file isBinary
  		ifTrue:
  			[startIndex to: startIndex + count - 1 do:
+ 				[ :i | file nextPut: (interpreterProxy byteAt: byteArrayIndex + i)]]
- 				[ :i | file nextPut: (interpreter byteAt: byteArrayIndex + i)]]
  		ifFalse:
  			[startIndex to: startIndex + count - 1 do:
  				[ :i | | byte |
+ 				byte := interpreterProxy byteAt: byteArrayIndex + i.
- 				byte := interpreter byteAt: byteArrayIndex + i.
  				file nextPut: (Character value: (byte == 12 "lf" ifTrue: [15"cr"] ifFalse: [byte]))]].
  	self recordStateOf: file.
  	^count!

Item was changed:
  ----- Method: SpurMemoryManager class>>ancilliaryClasses: (in category 'translation') -----
  ancilliaryClasses: options
+ 	initializationOptions ifNil: [initializationOptions := options].
  	^{	SpurGenerationScavenger. SpurSegmentManager. SpurSegmentInfo. self compactorClass },
  		SpurNewSpaceSpace withAllSubclasses!

Item was changed:
  ----- Method: StackInterpreter class>>initializeBytecodeTableForSqueakV3PlusClosures (in category 'initialization') -----
  initializeBytecodeTableForSqueakV3PlusClosures
  	"StackInterpreter initializeBytecodeTableForSqueakV3PlusClosures"
  	"Note: This table will be used to generate a C switch statement."
  
  	initializationOptions at: #SqueakV3PlusClosuresBytecodeSet put: (SqueakV3PlusClosuresBytecodeSet := true).
  
  	BytecodeTable := Array new: 256.
  	BytecodeEncoderClassName := #EncoderForV3PlusClosures.
  	LongStoreBytecode := 129.
+ 	BytecodeSetHasExtensions := false.
  	self table: BytecodeTable from:
  	#(
  		(  0  15 pushReceiverVariableBytecode)
  		( 16  31 pushTemporaryVariableBytecode)
  		( 32  63 pushLiteralConstantBytecode)
  		( 64  95 pushLiteralVariableBytecode)
  		( 96 103 storeAndPopReceiverVariableBytecode)
  		(104 111 storeAndPopTemporaryVariableBytecode)
  		(112 pushReceiverBytecode)
  		(113 pushConstantTrueBytecode)
  		(114 pushConstantFalseBytecode)
  		(115 pushConstantNilBytecode)
  		(116 pushConstantMinusOneBytecode)
  		(117 pushConstantZeroBytecode)
  		(118 pushConstantOneBytecode)
  		(119 pushConstantTwoBytecode)
  		(120 returnReceiver)
  		(121 returnTrue)
  		(122 returnFalse)
  		(123 returnNil)
  		(124 returnTopFromMethod)
  		(125 returnTopFromBlock)
  
  		(126 127 unknownBytecode)
  
  		(128 extendedPushBytecode)
  		(129 extendedStoreBytecode)
  		(130 extendedStoreAndPopBytecode)
  		(131 singleExtendedSendBytecode)
  		(132 doubleExtendedDoAnythingBytecode)
  		(133 singleExtendedSuperBytecode)
  		(134 secondExtendedSendBytecode)
  		(135 popStackBytecode)
  		(136 duplicateTopBytecode)
  
  		(137 pushActiveContextBytecode)
  		(138 pushNewArrayBytecode)),
  
  	((initializationOptions at: #SpurObjectMemory ifAbsent: [false])
  		ifTrue: [#((139 callPrimitiveBytecode))]	"V3PlusClosures on Spur"
  		ifFalse: [#((139 unknownBytecode))]),	"V3PlusClosures on V3"
  
  	  #(
  		(140 pushRemoteTempLongBytecode)
  		(141 storeRemoteTempLongBytecode)
  		(142 storeAndPopRemoteTempLongBytecode)
  		(143 pushClosureCopyCopiedValuesBytecode)
  
  		(144 151 shortUnconditionalJump)
  		(152 159 shortConditionalJumpFalse)
  		(160 167 longUnconditionalJump)
  		(168 171 longJumpIfTrue)
  		(172 175 longJumpIfFalse)
  
  		"176-191 were sendArithmeticSelectorBytecode"
  		(176 bytecodePrimAdd)
  		(177 bytecodePrimSubtract)
  		(178 bytecodePrimLessThan)
  		(179 bytecodePrimGreaterThan)
  		(180 bytecodePrimLessOrEqual)
  		(181 bytecodePrimGreaterOrEqual)
  		(182 bytecodePrimEqual)
  		(183 bytecodePrimNotEqual)
  		(184 bytecodePrimMultiply)
  		(185 bytecodePrimDivide)
  		(186 bytecodePrimMod)
  		(187 bytecodePrimMakePoint)
  		(188 bytecodePrimBitShift)
  		(189 bytecodePrimDiv)
  		(190 bytecodePrimBitAnd)
  		(191 bytecodePrimBitOr)
  
  		"192-207 were sendCommonSelectorBytecode"
  		(192 bytecodePrimAt)
  		(193 bytecodePrimAtPut)
  		(194 bytecodePrimSize)
  		(195 bytecodePrimNext)
  		(196 bytecodePrimNextPut)
  		(197 bytecodePrimAtEnd)
  		(198 bytecodePrimIdentical)
  		(199 bytecodePrimClass)
  		(200 bytecodePrimNotIdentical) "was bytecodePrimSpecialSelector24 / blockCopy"
  		(201 bytecodePrimValue)
  		(202 bytecodePrimValueWithArg)
  		(203 bytecodePrimDo)
  		(204 bytecodePrimNew)
  		(205 bytecodePrimNewWithArg)
  		(206 bytecodePrimPointX)
  		(207 bytecodePrimPointY)
  
  		(208 223 sendLiteralSelector0ArgsBytecode)
  		(224 239 sendLiteralSelector1ArgBytecode)
  		(240 255 sendLiteralSelector2ArgsBytecode)
  	)!

Item was changed:
  ----- Method: StackInterpreter>>initializeExtraClassInstVarIndices (in category 'initialization') -----
  initializeExtraClassInstVarIndices
  	"Initialize metaclassNumSlots and thisClassIndex which are used in debug printing, and
  	 classNameIndex which is used not only for debug printing but for is:KindOf: & is:MemberOf:
  	 via classNameOf:is: (evil but a reality we have to accept)."
  	| classArrayObj classArrayClass |
  	classArrayObj := objectMemory splObj: ClassArray.
  	classArrayClass := objectMemory fetchClassOfNonImm: classArrayObj.
  	metaclassNumSlots := objectMemory numSlotsOf: classArrayClass.	"determine actual Metaclass instSize"
  	thisClassIndex := 5. "default"
  	InstanceSpecificationIndex + 1 to: (objectMemory lengthOf: classArrayClass) do:
  		[:i|
  		(objectMemory fetchPointer: i - 1 ofObject: classArrayClass) = classArrayObj ifTrue:
  			[thisClassIndex := i - 1]].
  	classNameIndex := 6. "default"
  	InstanceSpecificationIndex + 1 to: (objectMemory lengthOf: classArrayObj) do:
  		[:i| | oop |
  		oop := objectMemory fetchPointer: i - 1 ofObject: classArrayObj.
  		((objectMemory isBytes: oop)
  		and: [(objectMemory lengthOf: oop) = 5
+ 		and: [(objectMemory str: 'Array' n: (objectMemory firstFixedField: oop) cmp: 5) = 0]]) ifTrue:
- 		and: [(self str: 'Array' n: (objectMemory firstFixedField: oop) cmp: 5) = 0]]) ifTrue:
  			[classNameIndex := i - 1]]!



More information about the Vm-dev mailing list