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

commits at source.squeak.org commits at source.squeak.org
Sat Nov 23 19:42:06 UTC 2019


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

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

Name: Cog-eem.370
Author: eem
Time: 23 November 2019, 11:42:05.121893 am
UUID: 27f27aaa-4b58-4e8e-81af-2d0d07950ca0
Ancestors: Cog-eem.369

Finish GdbARMv8AlienTests nfib tests by writing enough trap handling to handle the RET instruction.

=============== Diff against Cog-eem.369 ===============

Item was changed:
  CogProcessorAlien variableByteSubclass: #GdbARMv8Alien
  	instanceVariableNames: ''
+ 	classVariableNames: 'Level0FailureTable Level0OpcodeTable'
- 	classVariableNames: ''
  	poolDictionaries: ''
  	category: 'Cog-Processors'!
  
  !GdbARMv8Alien commentStamp: 'eem 11/19/2019 15:39' prior: 0!
  I am a wrapper around the struct sim aarch64 CPU instance and emulator routines and I give access to disassembling using libopcodes.!

Item was added:
+ ----- Method: GdbARMv8Alien class>>initialize (in category 'class initialization') -----
+ initialize
+ 	"Initialize the execution failure dispatch table.  This is organized around op0 in C4.1 of the Arm ARM.
+ 	 Each tuple is a type and a failure routine, or nil of not needed to be handled as an execution failure."
+ 	"self initialize"
+ 	Level0FailureTable := #(
+ 			"0"	nil nil nil nil
+ 			"4"	(LDST	handleFailingLoadStore:at:in:)
+ 			"5"	nil
+ 			"6"	(LDST	handleFailingLoadStore:at:in:)
+ 			"7"	nil nil nil
+ 			"a"	(BR		handleFailingBranch:at:in:)
+ 			"b"	(BR		handleFailingBranch:at:in:)
+ 			"c"	(LDST	handleFailingLoadStore:at:in:)
+ 			"d"	nil
+ 			"e"	(LDST	handleFailingLoadStore:at:in:)
+ 			nil)!

Item was added:
+ ----- Method: GdbARMv8Alien>>handleExecutionPrimitiveFailureIn:minimumAddress:code: (in category 'error handling') -----
+ handleExecutionPrimitiveFailureIn: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" code: errorCode "<Integer>"
+ 	"Handle an execution primitive failure.  Convert out-of-range call and absolute
+ 	 memory read into register instructions into ProcessorSimulationTrap signals."
+ 	"self printRegistersOn: Transcript"
+ 	| instr pc op |
+ 	pc := self pc.
+ 	instr := self instr.
+ 	(pc between: minimumAddress and: memoryArray byteSize - 1) ifTrue:
+ 		[self assert: self instr = (memoryArray unsignedLongAt: pc + 1 bigEndian: false)].
+ 	op := self instr >> 25 bitAnd: 16rF.
+ 	(Level0FailureTable at: op + 1) ifNotNil:
+ 		[:tuple|
+ 		^self perform: tuple last with: instr with: pc with: memoryArray].
+ 	^self reportPrimitiveFailure!

Item was added:
+ ----- Method: GdbARMv8Alien>>handleFailingBranch:at:in: (in category 'error handling') -----
+ handleFailingBranch: instruction at: pc in: memoryArray "<Bitmap|ByteArray>"
+ 	"see C4.1.3 Branches, Exception Generating and System instructions in Arm ARM.
+ 	 Table C4-4 op1 plus the two top bit of op1"
+ 	| decode |
+ 	decode := ((instruction bitShift: -29) bitShift: 1) + ((instruction bitShift: -25) bitAnd: 1).
+ 	decode = 2r1101 ifTrue: "Unconditional branch (register) on page C4-262"
+ 		[instruction = 2r11010110010111110000001111000000 ifTrue:
+ 			[^(ProcessorSimulationTrap
+ 				pc: pc
+ 				nextpc: pc + 4
+ 				address: self lr
+ 				type: #return)
+ 			signal]].
+ 	self reportPrimitiveFailure!

Item was added:
+ ----- Method: GdbARMv8Alien>>instr (in category 'accessing') -----
+ instr
+ 	^self unsignedLongAt: 809!

Item was changed:
  ----- Method: GdbARMv8Alien>>primitiveRunInMemory:minimumAddress:readOnlyBelow: (in category 'primitives') -----
  primitiveRunInMemory: memoryArray "<Bitmap|ByteArray>" minimumAddress: minimumAddress "<Integer>" readOnlyBelow: minimumWritableAddress "<Integer>"
  	"Run the receiver using the argument as the store.  Origin the argument at 0. i.e. the first byte of the
  	 memoryArray is address 0.  Make addresses below minimumAddress illegal.  Convert out-of-range
  	 calls, jumps and memory read/writes into ProcessorSimulationTrap signals.
  	Note that minWriteMaxExecAddress is both the minimum writeable address AND the maximum executable address"
  	<primitive: 'primitiveRunInMemoryMinimumAddressReadWrite' module: 'GdbARMv8Plugin' error: ec>
+ 	^ec isPrimitiveError
+ 		ifTrue:
+ 			[self handleExecutionPrimitiveFailureIn: memoryArray
+ 				minimumAddress: minimumAddress
+ 				code: ec errorCode]
+ 		ifFalse:
+ 			[ec == #'inappropriate operation'
+ 				ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
+ 							minimumAddress: minimumAddress]
+ 				ifFalse: [self reportPrimitiveFailure]]
- 	^ec == #'inappropriate operation'
- 		ifTrue: [self handleExecutionPrimitiveFailureIn: memoryArray
- 					minimumAddress: minimumAddress]
- 		ifFalse: [self reportPrimitiveFailure]
  
  	"self printRegistersOn: Transcript"!

Item was changed:
  ----- Method: GdbARMv8AlienTests>>runNFib:disassemble:printRegisters: (in category 'private') -----
  runNFib: n disassemble: disassemble printRegisters: printRegisters
  	"Run nfib wth the argument. Answer the result."
  	"self new runNFib: 5 disassemble: true printRegisters: true"
  	| memory |
+ 	memory := LittleEndianBitmap new: 1024 * 2 withAll: self processor nopOpcode.
- 	memory := Bitmap new: 1024 * 2 withAll: self processor nopOpcode.
  	memory replaceFrom: 1 to: self nfib size with: self nfib asWordArray startingAt: 1.
  	self processor
  		r0: n;"argument n"
  		lr: memory size * 2; "return address"
  		pc: 0;
  		sp: (memory size * 4) - 16.
  	printRegisters ifTrue:
  		[self processor printRegistersOn: Transcript.
  		 Transcript cr; flush].
  	"run until something goes wrong."
  	self processor runInMemory: memory readExecuteOnlyBelow: memory size / 2.
  	printRegisters ifTrue:
  		[self processor printRegistersOn: Transcript.
  		 Transcript cr; flush].
  	^self processor r0!

Item was changed:
  ----- Method: GdbARMv8AlienTests>>testNfib1 (in category 'tests') -----
  testNfib1
  	"self new testNfib1"
  	self should: [self runNFib: 1 disassemble: false printRegisters: false]
  		raise: Error
  		withExceptionDo: 
+ 			[:err|
+ 			 self assert: err class = ProcessorSimulationTrap.
+ 			 self assert: #return = err type.
+ 			 self assert: 16r1000 equals: err address].
- 			[:err| self assert: err messageText = 'Error 0: Illegal Instruction fetch address (0x1000).'].
  	self deny: (self processor pc between: 0 and: self nfib size).
  	self assert: self processor r0 = 1 benchFib!



More information about the Vm-dev mailing list