[Vm-dev] VM Maker: Cog-rmacnak.295.mcz

commits at source.squeak.org commits at source.squeak.org
Sun Nov 15 23:53:53 UTC 2015


Ryan Macnak uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-rmacnak.295.mcz

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

Name: Cog-rmacnak.295
Author: rmacnak
Time: 15 November 2015, 3:53:37.223 pm
UUID: 85274ec7-5fe4-4e2c-9e11-1890f49aae4e
Ancestors: Cog-rmacnak.294

Get MIPSEL up to the first page fault accessing an interpreter variable.

Add base-bound checks for readable/writable/executable memory.
Implement more of the processor alien API.

=============== Diff against Cog-rmacnak.294 ===============

Item was changed:
  ----- Method: MIPSDisassembler>>disassemble:from:to:for:labels:on: (in category 'as yet unclassified') -----
  disassemble: memory from: startPC to: limitPC for: aSymbolManager "<Cogit>" labels: labelDictionary on: aStream
+ 	aStream print: labelDictionary;cr.
  	pc := startPC.
  	[pc < limitPC] whileTrue:
  		[ | word instruction |
  		pc printOn: aStream base: 16 nDigits: 8.
  		aStream space; space.
  		word := memory unsignedLongAt: pc + 1.
  		word printOn: aStream base: 16 nDigits: 8.
  		aStream space; space.
  		instruction := MIPSInstruction new value: word.
  		aStream nextPutAll: (instruction decodeFor: self).
  		aStream cr.
  		pc := pc + OneInstruction].!

Item was added:
+ ----- Method: MIPSELSimulator>>fetchInstruction: (in category 'as yet unclassified') -----
+ fetchInstruction: address
+ 	address < exectuableBase ifTrue: [self executeFault: address].
+ 	address > exectuableLimit ifTrue: [self executeFault: address].
+ 	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	^memory unsignedLongAt: address + 1 bigEndian: false!

Item was added:
+ ----- Method: MIPSELSimulator>>readFault: (in category 'as yet unclassified') -----
+ readFault: address
+ 	^(ProcessorSimulationTrap
+ 			pc: pc
+ 			nextpc: pc + 4
+ 			address: address
+ 			type: #read
+ 			accessor: nil)
+ 		signal
+ !

Item was changed:
  ----- Method: MIPSELSimulator>>signedByte: (in category 'as yet unclassified') -----
  signedByte: address
+ 	address < readableBase ifTrue: [self readFault: address].
+ 	address > readableLimit ifTrue: [self readFault: address].
  	^memory signedByteAt: address + 1!

Item was changed:
  ----- Method: MIPSELSimulator>>signedByte:put: (in category 'memory') -----
  signedByte: address put: value
+ 	address < writableBase ifTrue: [self writeFault: address].
+ 	address > writableLimit ifTrue: [self writeFault: address].
  	^memory signedByteAt: address + 1 put: value!

Item was changed:
  ----- Method: MIPSELSimulator>>signedHalfword: (in category 'as yet unclassified') -----
  signedHalfword: address
  	(address bitAnd: 1) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	address < readableBase ifTrue: [self readFault: address].
+ 	address > readableLimit ifTrue: [self readFault: address].
  	^memory signedShortAt: address + 1!

Item was changed:
  ----- Method: MIPSELSimulator>>signedHalfword:put: (in category 'memory') -----
  signedHalfword: address put: value
  	(address bitAnd: 1) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	address < writableBase ifTrue: [self writeFault: address].
+ 	address > writableLimit ifTrue: [self writeFault: address].
  	^memory signedShortAt: address + 1 put: value!

Item was changed:
  ----- Method: MIPSELSimulator>>signedWord: (in category 'as yet unclassified') -----
  signedWord: address
  	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	address < readableBase ifTrue: [self readFault: address].
+ 	address > readableLimit ifTrue: [self readFault: address].		
+ 	^memory longAt: address + 1!
- 	^memory signedLongAt: address + 1!

Item was changed:
  ----- Method: MIPSELSimulator>>signedWord:put: (in category 'memory') -----
  signedWord: address put: value
  	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	address < writableBase ifTrue: [self writeFault: address].
+ 	address > writableLimit ifTrue: [self writeFault: address].
  	^memory signedLongAt: address + 1 put: value!

Item was removed:
- ----- Method: MIPSELSimulator>>snsignedWord: (in category 'as yet unclassified') -----
- snsignedWord: address
- 	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
- 	^memory unsignedLongAt: address + 1 bigEndian: false!

Item was changed:
  ----- Method: MIPSELSimulator>>unsignedByte: (in category 'as yet unclassified') -----
  unsignedByte: address
+ 	address < readableBase ifTrue: [self readFault: address].
+ 	address > readableLimit ifTrue: [self readFault: address].
  	^memory at: address + 1!

Item was changed:
  ----- Method: MIPSELSimulator>>unsignedByte:put: (in category 'memory') -----
  unsignedByte: address put: value
+ 	address < writableBase ifTrue: [self writeFault: address].
+ 	address > writableLimit ifTrue: [self writeFault: address].
  	^memory at: address + 1 put: value!

Item was changed:
  ----- Method: MIPSELSimulator>>unsignedHalfword: (in category 'as yet unclassified') -----
  unsignedHalfword: address
+ 	address < readableBase ifTrue: [self readFault: address].
+ 	address > readableLimit ifTrue: [self readFault: address].
  	(address bitAnd: 1) = 0 ifFalse: [self error: 'Unaligned read'].
  	^memory unsignedShortAt: address + 1 bigEndian: false!

Item was changed:
  ----- Method: MIPSELSimulator>>unsignedHalfword:put: (in category 'memory') -----
  unsignedHalfword: address put: value
  	(address bitAnd: 1) = 0 ifFalse: [self error: 'Unaligned read'].
+ 	address < writableBase ifTrue: [self writeFault: address].
+ 	address > writableLimit ifTrue: [self writeFault: address].
  	^memory unsignedShortAt: address + 1 put: value!

Item was changed:
  ----- Method: MIPSELSimulator>>unsignedWord: (in category 'as yet unclassified') -----
  unsignedWord: address
+ 	address < readableBase ifTrue: [self readFault: address].
+ 	address > readableLimit ifTrue: [self readFault: address].
  	(address bitAnd: 3) = 0 ifFalse: [self error: 'Unaligned read'].
  	^memory unsignedLongAt: address + 1 bigEndian: false!

Item was changed:
  Object subclass: #MIPSSimulator
+ 	instanceVariableNames: 'memory registers pc instructionCount inDelaySlot readableBase writableBase exectuableBase readableLimit writableLimit exectuableLimit'
- 	instanceVariableNames: 'memory registers pc instructionCount inDelaySlot'
  	classVariableNames: 'EndSimulationPC'
  	poolDictionaries: 'MIPSConstants'
  	category: 'Cog-Processors'!
  
  !MIPSSimulator commentStamp: 'rmacnak 11/11/2015 20:33:00' prior: 0!
  Simulator for 32-bit MIPS, without implementation of memory access.!

Item was added:
+ ----- Method: MIPSSimulator>>convertIntegerToInternal: (in category 'processor api') -----
+ convertIntegerToInternal: anInteger
+ 	"Default conversion for 32-bit processors.  64-bit processors override."
+ 	^anInteger signedIntToLong!

Item was added:
+ ----- Method: MIPSSimulator>>currentInstruction (in category 'as yet unclassified') -----
+ currentInstruction
+ 	^[(MIPSDisassembler new disassemble: memory from: pc to: pc + 4)]
+ 		ifError: ['Cannot disassemble'].!

Item was changed:
  ----- Method: MIPSSimulator>>execute (in category 'as yet unclassified') -----
  execute
  	| instruction |
  	[pc ~= EndSimulationPC] whileTrue: 
+ 		[Transcript nextPutAll: '* '; nextPutAll: self currentInstruction; flush.
+ 		 instruction := MIPSInstruction new value: (self fetchInstruction: pc).
- 		[instruction := MIPSInstruction new value: (self unsignedWord: pc).
  		 instruction decodeFor: self.
  		 pc := pc + OneInstruction].!

Item was changed:
  ----- Method: MIPSSimulator>>executeDelaySlot (in category 'as yet unclassified') -----
  executeDelaySlot
  	| instruction |
  	self assert: inDelaySlot not.
  	inDelaySlot := true.
+ 	instruction := MIPSInstruction new value: (self fetchInstruction: pc).
- 	instruction := MIPSInstruction new value: (self unsignedWord: pc).
  	instruction decodeFor: self.
  	inDelaySlot := false.!

Item was added:
+ ----- Method: MIPSSimulator>>initialize (in category 'as yet unclassified') -----
+ initialize
+ 	registers := Array new: 32 withAll: 16rABABAB.
+ 	pc := 0.
+ 	inDelaySlot := false.
+ 	instructionCount := 0.!

Item was changed:
  ----- Method: MIPSSimulator>>initializeStackFor: (in category 'processor api') -----
  initializeStackFor: aCogit
  	self flag: #OABI.
  	aCogit setStackAlignment: 8 expectedSPOffset: 0 expectedFPOffset: 0.
- 	self initializeWithMemory: ByteArray new.
  	!

Item was changed:
  ----- Method: MIPSSimulator>>initializeWithMemory: (in category 'as yet unclassified') -----
  initializeWithMemory: aByteArray
+ 	memory := aByteArray.!
- 	memory := aByteArray.
- 	registers := Array new: 32 withAll: 0.
- 	pc := 0.
- 	inDelaySlot := false.
- 	instructionCount := 0.!

Item was added:
+ ----- Method: MIPSSimulator>>pc: (in category 'processor api') -----
+ pc: newPC
+ 	pc := newPC.!

Item was changed:
  ----- Method: MIPSSimulator>>printOn: (in category 'as yet unclassified') -----
  printOn: stream
  	stream nextPutAll: self class name; nextPut: $:; cr.
  	0 to: 31 do:
  		[:reg | | hex |
  		stream space.
  		stream nextPutAll: (MIPSConstants nameForRegister: reg).
  		stream space.
  		hex := (self unsignedRegister: reg) printStringBase: 16.
  		8 - hex size timesRepeat: [stream nextPut: $0].
  		stream nextPutAll: hex.
  		stream space.
  		(self signedRegister: reg) printOn: stream.
  		stream cr].
+ 	
+ 	stream nextPutAll: self currentInstruction.!
- 	!

Item was added:
+ ----- Method: MIPSSimulator>>runInMemory:minimumAddress:readOnlyBelow: (in category 'processor api') -----
+ runInMemory: aMemory minimumAddress: minimumAddress readOnlyBelow: minimumWritableAddress
+ 	"Note that minimumWritableAddress is both the minimum writeable address AND the maximum executable address"
+ 	memory := aMemory.
+ 	readableBase := minimumAddress.
+ 	writableBase := minimumWritableAddress.
+ 	exectuableBase := minimumAddress.
+ 	readableLimit := aMemory size.
+ 	writableLimit := aMemory size.
+ 	exectuableLimit := minimumWritableAddress.
+ 	self execute.!

Item was changed:
  ----- Method: MIPSSimulator>>setFramePointer:stackPointer: (in category 'processor api') -----
  setFramePointer: fp stackPointer: sp
  	self signedRegister: SP put: sp.
  	self signedRegister: FP put: fp.!

Item was changed:
  ----- Method: MIPSSimulator>>signedRegister: (in category 'registers') -----
+ signedRegister: registerNumber
- signedRegister: registerNumber 
  	registerNumber == ZR ifTrue: [^0] ifFalse: [^registers at: registerNumber + 1].!

Item was changed:
  ----- Method: MIPSSimulator>>signedRegister:put: (in category 'registers') -----
  signedRegister: registerNumber put: signedValue
  	self assert: (signedValue between: -16r80000000 and: 16r7FFFFFFF).
  	registerNumber == ZR ifFalse: [registers at: registerNumber + 1 put: signedValue].!

Item was added:
+ ----- Method: MIPSSimulator>>simulateLeafCallOf:nextpc:memory: (in category 'processor api') -----
+ simulateLeafCallOf: address nextpc: nextpc memory: aMemory
+ 	self signedRegister: RA put: nextpc.
+ 	pc := address.!

Item was added:
+ ----- Method: MIPSSimulator>>smashRegistersWithValuesFrom:by: (in category 'processor api') -----
+ smashRegistersWithValuesFrom: base by: step
+ 	"Ignore this - we do a stronger check later."!

Item was changed:
  ----- Method: MIPSSimulator>>sp (in category 'processor api') -----
  sp
  	^self signedRegister: SP!

Item was changed:
  ----- Method: MIPSSimulator>>unsignedRegister: (in category 'registers') -----
  unsignedRegister: registerNumber
  	registerNumber == ZR 
  		ifTrue: [^0]
  		ifFalse: [^self signed32ToUnsigned32: (registers at: registerNumber + 1)].!

Item was changed:
  ----- Method: MIPSSimulator>>unsignedRegister:put: (in category 'registers') -----
  unsignedRegister: registerNumber put: unsignedValue
  	registerNumber == ZR ifFalse:
  		[registers at: registerNumber + 1 put: (self unsigned32ToSigned32: unsignedValue)].!



More information about the Vm-dev mailing list