[Vm-dev] VM Maker: Cog-eem.369.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Nov 22 21:03:08 UTC 2019


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

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

Name: Cog-eem.369
Author: eem
Time: 22 November 2019, 1:03:06.271882 pm
UUID: f98a0c3b-0dbe-42ae-8210-d628f7f84b98
Ancestors: Cog-eem.368

Speed up marshalling for the ProcessorSimulatorPlugins by using SmallInteger for the memory range arguments instead of Unsigned.  Using the latest Slang changes this inlines a lot of code and reduces function calls to decode the range arguments.  Given that the memory range arguments are always within the range of the memory byte array, SmallIntegers provide more than enough range.

More substantively use primitiveFailForOSError: to answer the failure error code, if any, on simulating.

=============== Diff against Cog-eem.368 ===============

Item was added:
+ ----- Method: ProcessorSimulatorPlugin class>>preambleCCode (in category 'translation') -----
+ preambleCCode
+ 	"Whoreish SmallInteger acess macros to speed up marshalling."
+ 	^String streamContents: [:s| self codeGeneratorClass new preDeclareMacrosForFastClassCheckingOn: s guardWith: nil]!

Item was changed:
  ----- Method: ProcessorSimulatorPlugin>>primitiveDisassembleAt:InMemory: (in category 'primitives') -----
  "cpuAlien <BochsIA32|X86Alien>" primitiveDisassembleAt: address "<Integer>" InMemory: memory "<Bitmap|ByteArray|WordArray>"
  	"Return an Array of the instruction length and its decompilation as a string for the instruction at address in memory."
  	| cpuAlien cpu instrLenOrErr resultObj log logLen logObj logObjData |
  	<var: #cpu type: #'void *'>
  	<var: #log type: #'char *'>
  	<var: #logLen type: #long>
  	<var: #logObjData type: #'char *'>
  	cpuAlien := self primitive: #primitiveDisassembleAtInMemory
+ 					parameters: #(SmallInteger WordsOrBytes)
- 					parameters: #(Unsigned WordsOrBytes)
  					receiver: #Oop.
  	(cpu := self cCoerceSimple: (self startOfData: cpuAlien) to: #'void *') = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	instrLenOrErr := self disassembleFor: cpu
  						At: address
  						In: memory
  						Size: (interpreterProxy byteSizeOf: memory cPtrAsOop).
  	instrLenOrErr < 0 ifTrue:
+ 		[^interpreterProxy primitiveFailForOSError: instrLenOrErr negated].
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	log := self getlog: (self cCode: [self addressOf: logLen] inSmalltalk: [logLen := 0]).
  	resultObj := interpreterProxy instantiateClass: interpreterProxy classArray indexableSize: 2.
  	resultObj = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  
  	"Easier keeping the damn thing on the stack than using pushRemappableOop:/popRemappableOop.
  	 Where is topRemappableOop when you need it?"
  	interpreterProxy pushRemappableOop: resultObj.
  	logObj := interpreterProxy
  				instantiateClass: interpreterProxy classString
  				indexableSize: logLen.
  	interpreterProxy failed ifTrue:
  		[interpreterProxy popRemappableOop.
  		 ^interpreterProxy primitiveFailFor: PrimErrNoMemory].
  	logObjData := interpreterProxy arrayValueOf: logObj.
  	self mem: logObjData cp: log y: logLen.
  	resultObj := interpreterProxy popRemappableOop.
  	interpreterProxy
  		storePointer: 0
  		ofObject: resultObj
  		withValue: (interpreterProxy integerObjectOf: instrLenOrErr).
  	interpreterProxy storePointer: 1 ofObject: resultObj withValue: logObj.
  
  	^resultObj!

Item was changed:
  ----- Method: ProcessorSimulatorPlugin>>primitiveFlushICacheFrom:To: (in category 'primitives') -----
  "cpuAlien <BochsIA32|X86Alien>" primitiveFlushICacheFrom: startAddress "<Integer>" To: endAddress "<Integer>"
  	"Flush the icache in the requested range"
  	| cpuAlien cpu |
  	<var: #cpu type: #'void *'>
  	cpuAlien := self primitive: #primitiveFlushICacheFromTo
+ 					parameters: #(SmallInteger SmallInteger)
- 					parameters: #(Unsigned Unsigned)
  					receiver: #Oop.
  	(cpu := self cCoerceSimple: (self startOfData: cpuAlien) to: #'void *') = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	self flushICache: cpu From: startAddress To: endAddress!

Item was changed:
  ----- Method: ProcessorSimulatorPlugin>>primitiveResetCPU (in category 'primitives') -----
  primitiveResetCPU
  	| cpuAlien cpu maybeErr |
  	<var: #cpu type: #'void *'>
  	cpuAlien := self primitive: #primitiveResetCPU parameters: #() receiver: #Oop.
  	(cpu := self cCoerceSimple: (self startOfData: cpuAlien) to: #'void *') = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
  	maybeErr := self resetCPU: cpu.
  	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailForOSError: maybeErr].
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	^cpuAlien!

Item was changed:
  ----- Method: ProcessorSimulatorPlugin>>primitiveRunInMemory:minimumAddress:maximumAddress:readOnlyBelow: (in category 'primitives') -----
  "cpuAlien <BochsIA32|X86Alien>" primitiveRunInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" maximumAddress: maxAddress "<Integer>" readOnlyBelow: minWriteMaxExecAddress "<Integer>"
  	"Run the cpu using the first argument as the memory and the following arguments defining valid addresses, running until it halts or hits an exception."
  	| cpuAlien cpu memorySize maybeErr |
  	<var: #cpu type: #'void *'>
  	cpuAlien := self primitive: #primitiveRunInMemoryMinAddressMaxAddressReadWrite
+ 					parameters: #(WordsOrBytes SmallInteger SmallInteger SmallInteger)
- 					parameters: #(WordsOrBytes Unsigned Unsigned Unsigned)
  					receiver: #Oop.
  	(cpu := self cCoerceSimple: (self startOfData: cpuAlien) to: #'void *') = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	(minAddress < 0
+ 	or: [maxAddress < 0
+ 	or: [minWriteMaxExecAddress < 0]]) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
  	"Add forceStopOnInterrupt to the interrupt check chain.  It is our responsibility to
  	 chain calls, hence we remember any previous client in prevInterruptCheckChain."
  	prevInterruptCheckChain := interpreterProxy setInterruptCheckChain: #forceStopOnInterrupt asSymbol.
  	prevInterruptCheckChain = #forceStopOnInterrupt asSymbol ifTrue:
  		[prevInterruptCheckChain := 0].
  	memorySize := interpreterProxy byteSizeOf: memory cPtrAsOop.
  	maybeErr := self runCPU: cpu
  					In: memory
  					Size: (memorySize min: maxAddress)
  					MinAddressRead: minAddress
  					Write: minWriteMaxExecAddress.
  	interpreterProxy setInterruptCheckChain: prevInterruptCheckChain.
  	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailForOSError: maybeErr].
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	^cpuAlien!

Item was changed:
  ----- Method: ProcessorSimulatorPlugin>>primitiveRunInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
  "cpuAlien <BochsIA32|X86Alien>" primitiveRunInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" readOnlyBelow: minWriteMaxExecAddress "<Integer>"
  	"Run the cpu using the first argument as the memory and the following arguments defining valid addresses, running until it halts or hits an exception."
  	| cpuAlien cpu maybeErr |
  	<var: #cpu type: #'void *'>
  	cpuAlien := self primitive: #primitiveRunInMemoryMinimumAddressReadWrite
+ 					parameters: #(WordsOrBytes SmallInteger SmallInteger)
- 					parameters: #(WordsOrBytes Unsigned Unsigned)
  					receiver: #Oop.
  	(cpu := self cCoerceSimple: (self startOfData: cpuAlien) to: #'void *') = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	(minAddress < 0
+ 	or: [minWriteMaxExecAddress < 0]) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
  	prevInterruptCheckChain := interpreterProxy setInterruptCheckChain: #forceStopOnInterrupt asSymbol.
  	prevInterruptCheckChain = #forceStopOnInterrupt asSymbol ifTrue:
  		[prevInterruptCheckChain := 0].
  	maybeErr := self runCPU: cpu
  					In: memory
  					Size: (interpreterProxy byteSizeOf: memory cPtrAsOop)
  					MinAddressRead: minAddress
  					Write: minWriteMaxExecAddress.
  	interpreterProxy setInterruptCheckChain: prevInterruptCheckChain.
  	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailForOSError: maybeErr].
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	^cpuAlien!

Item was changed:
  ----- Method: ProcessorSimulatorPlugin>>primitiveSingleStepInMemory:minimumAddress:maximumAddress:readOnlyBelow: (in category 'primitives') -----
  "cpuAlien <BochsIA32|X86Alien>" primitiveSingleStepInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>" maximumAddress: maxAddress "<Integer>" readOnlyBelow: minWriteMaxExecAddress "<Integer>"
  	"Single-step the cpu using the first argument as the memory and the following arguments defining valid addresses."
  	| cpuAlien cpu memorySize maybeErr |
  	<var: #cpu type: #'void *'>
  	cpuAlien := self primitive: #primitiveSingleStepInMemoryMinAddressMaxAddressReadWrite
+ 					parameters: #(WordsOrBytes SmallInteger SmallInteger SmallInteger)
- 					parameters: #(WordsOrBytes Unsigned Unsigned Unsigned)
  					receiver: #Oop.
  	(cpu := self cCoerceSimple: (self startOfData: cpuAlien) to: #'void *') = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	(minAddress < 0
+ 	or: [maxAddress < 0
+ 	or: [minWriteMaxExecAddress < 0]]) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
  	memorySize := interpreterProxy byteSizeOf: memory cPtrAsOop.
  	maybeErr := self singleStepCPU: cpu
  					In: memory
  					Size: (memorySize min: maxAddress)
  					MinAddressRead: minAddress
  					Write: minWriteMaxExecAddress.
  	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailForOSError: maybeErr].
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	^cpuAlien!

Item was changed:
  ----- Method: ProcessorSimulatorPlugin>>primitiveSingleStepInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
  "cpuAlien <BochsIA32|X86Alien>" primitiveSingleStepInMemory: memory "<Bitmap|ByteArray|WordArray>" minimumAddress: minAddress "<Integer>"  readOnlyBelow: minWriteMaxExecAddress "<Integer>"
  	"Single-step the cpu using the first argument as the memory and the following arguments defining valid addresses."
  	| cpuAlien cpu maybeErr |
  	<var: #cpu type: #'void *'>
  	cpuAlien := self primitive: #primitiveSingleStepInMemoryMinimumAddressReadWrite
+ 					parameters: #(WordsOrBytes SmallInteger SmallInteger)
- 					parameters: #(WordsOrBytes Unsigned Unsigned)
  					receiver: #Oop.
  	(cpu := self cCoerceSimple: (self startOfData: cpuAlien) to: #'void *') = 0 ifTrue:
  		[^interpreterProxy primitiveFailFor: PrimErrBadReceiver].
+ 	(minAddress < 0
+ 	or: [minWriteMaxExecAddress < 0]) ifTrue:
+ 		[^self primitiveFailFor: PrimErrBadArgument].
  	maybeErr := self singleStepCPU: cpu
  					In: memory
  					Size: (interpreterProxy byteSizeOf: memory cPtrAsOop)
  					MinAddressRead: minAddress
  					Write: minWriteMaxExecAddress.
  	maybeErr ~= 0 ifTrue:
+ 		[^interpreterProxy primitiveFailForOSError: maybeErr].
- 		[^interpreterProxy primitiveFailFor: PrimErrInappropriate].
  	^cpuAlien!



More information about the Vm-dev mailing list