[Vm-dev] VM Maker: Cog-tpr.253.mcz

commits at source.squeak.org commits at source.squeak.org
Thu Mar 26 22:32:39 UTC 2015


tim Rowledge uploaded a new version of Cog to project VM Maker:
http://source.squeak.org/VMMaker/Cog-tpr.253.mcz

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

Name: Cog-tpr.253
Author: tpr
Time: 26 March 2015, 3:32:27.212 pm
UUID: 4619166e-331d-4725-85f3-124619991442
Ancestors: Cog-eem.252

convert various methods to refer to 'sl' instead of 'r10' since that is what we print out in debugging messages. 
Clean up a couple of alien tests

=============== Diff against Cog-eem.252 ===============

Item was changed:
  ----- Method: GdbARMAlien>>integerRegisterState (in category 'accessing-abstract') -----
  integerRegisterState
  	^{	self r0. self r1. self r2. self r3. self r4. self r5. self r6. self r7. self r8. 
+ 		self r9. self sl. self fp. self r12. self sp. self lr. self pc}!
- 		self r9. self r10. self fp. self r12. self sp. self lr. self pc}!

Item was removed:
- ----- Method: GdbARMAlien>>postTrapCorrectedPC (in category 'accessing') -----
- postTrapCorrectedPC
- 	"return the pc - 8 for trap handling - remember the ARM alwayshas that funky +8 offset vs the actual instruction running/failig"
- 	^self pc -8!

Item was changed:
  ----- Method: GdbARMAlien>>printRegisterState:on: (in category 'printing') -----
  printRegisterState: registerStateVector on: aStream
  	self printFields: #(	r0 r1 r2 r3 cr
  						r4 r5 r6 r7 cr
+ 						r8 r9 sl fp cr
- 						r8 r9 r10 fp cr
  						r12 sp lr pc eflags cr)
  		inRegisterState: registerStateVector
  		on: aStream!

Item was changed:
  ----- Method: GdbARMAlien>>printRegisterStateExceptPC:on: (in category 'printing') -----
  printRegisterStateExceptPC: registerStateVector on: aStream
  	self printFields: #(	r0 r1 r2 r3 cr
  						r4 r5 r6 r7 cr
+ 						r8 r9 sl fp cr
- 						r8 r9 r10 fp cr
  						r12 sp lr eflags cr)
  		inRegisterState: registerStateVector
  		on: aStream!

Item was added:
+ ----- Method: GdbARMAlien>>priorPc: (in category 'accessing') -----
+ priorPc: val
+ "set the priorPC cached pc so it isn't random nonsense"
+ 	^self unsignedLongAt: 609 put: val!

Item was changed:
  ----- Method: GdbARMAlien>>r10 (in category 'accessing') -----
  r10
+ 	^self sl!
- 	^self unsignedLongAt: 53!

Item was changed:
  ----- Method: GdbARMAlien>>r10: (in category 'accessing') -----
  r10: anUnsignedInteger
  
+ 	^self sl: anUnsignedInteger!
- 	^self unsignedLongAt: 53 put: anUnsignedInteger!

Item was changed:
  ----- Method: GdbARMAlien>>registerState (in category 'accessing-abstract') -----
  registerState
  	^{	self r0. self r1. self r2. self r3. self r4. self r5. self r6. self r7.
+ 		self r8. self r9. self sl. self fp. self r12. self sp. self lr. self pc. self eflags }!
- 		self r8. self r9. self r10. self fp. self r12. self sp. self lr. self pc. self eflags }!

Item was changed:
  ----- Method: GdbARMAlien>>registerStateNames (in category 'accessing-abstract') -----
  registerStateNames
+ 	^#(	r0 r1 r2 r3 r4 r5 r6 r7 r8 r9 sl fp r12 sp lr pc eflags)!
- 	^#(	r0 r1 r2 r3 r4 r5 r6 r7 r8 r9 r10 fp r12 sp lr pc eflags)!

Item was changed:
  ----- Method: GdbARMAlien>>registerStateSetters (in category 'accessing-abstract') -----
  registerStateSetters
  "a list of register setting messages used to initialise or reset registers"
+ 	^#(	r0: r1: r2: r3: r4: r5: r6: r7: r8: r9: sl: fp: r12: sp: lr: pc: eflags:)!
- 	^#(	r0: r1: r2: r3: r4: r5: r6: r7: r8: r9: r10: fp: r12: sp: lr: pc: eflags:)!

Item was changed:
  ----- Method: GdbARMAlien>>reset (in category 'accessing') -----
  reset
+ 	self priorPc: 0;
+ 		primitiveResetCPU!
- 	self primitiveResetCPU!

Item was added:
+ ----- Method: GdbARMAlien>>sl (in category 'accessing') -----
+ sl
+ 	^self unsignedLongAt: 53!

Item was added:
+ ----- Method: GdbARMAlien>>sl: (in category 'accessing') -----
+ sl: anUnsignedInteger
+ 
+ 	^self unsignedLongAt: 53 put: anUnsignedInteger!

Item was changed:
  ----- Method: GdbARMAlien>>writePopPushDetailsIn:in:for: (in category 'printing') -----
  writePopPushDetailsIn: memory in: transcript for: aCogit 
  	"if the next instruction is a pop or push, or a ldr/str that touches the
  	SP, write the details ontranscript"
  	| instr |
  	[instr := memory unsignedLongAt: self pc + 1 bigEndian: false]
  		on: Error
  		do: [:ex | ^ self].
  	(self instructionIsPop: instr)
  		ifTrue: [^transcript tab; nextPutAll: 'POP ' , (memory unsignedLongAt: self sp + 1 bigEndian: false) hex , ' from ' , self sp hex; cr].
  	(self instructionIsPush: instr)
  		ifTrue: [^transcript tab; nextPutAll: 'PUSH ' , (self register: (instr bitAnd: 61440)
  							>> 12) hex , ' to ' , (self sp - 4) hex; cr].
  	(self instructionIsLDRSP: instr)
  		ifTrue: [| val |
+ 			val := self sl > memory size
+ 						ifTrue: [aCogit simulatedVariableAt: self sl]
+ 						ifFalse: [memory unsignedLongAt: self sl + 1 bigEndian: false].
+ 			^transcript tab; nextPutAll: 'LOAD SP ' , val hex , ' from ' , self sl hex; cr].
- 			val := self r10 > memory size
- 						ifTrue: [aCogit simulatedVariableAt: self r10]
- 						ifFalse: [memory unsignedLongAt: self r10 + 1 bigEndian: false].
- 			^transcript tab; nextPutAll: 'LOAD SP ' , val hex , ' from ' , self r10 hex; cr].
  	(self instructionIsSTRSP: instr)
+ 		ifTrue: [^transcript tab; nextPutAll: 'STORE SP ' , self sp hex , ' to ' , self sl hex; cr].
- 		ifTrue: [^transcript tab; nextPutAll: 'STORE SP ' , self sp hex , ' to ' , self r10 hex; cr].
  	(self instructionIsAlignSP: instr)
  		ifTrue: [^transcript tab; nextPutAll: 'ALIGN SP ' , self sp hex; cr].
  	(self instructionIsAddSP: instr) ifTrue:[^transcript tab; nextPutAll: 'ADD ', (instr bitAnd: 16rFF) asString,' to SP = ' , self sp hex; cr]!

Item was changed:
  ----- Method: GdbARMAlienTests>>integerRegisterGetters (in category 'accessing') -----
  integerRegisterGetters
+ 	^#(r0 r1 r2 r3 r4 r5 r6 r7 r8 r9 sl fp r12 lr sp pc)!
- 	^#(r0 r1 r2 r3 r4 r5 r6 r7 r8 r9 r10 fp r12 lr sp pc)!

Item was changed:
  ----- Method: GdbARMAlienTests>>memory (in category 'accessing') -----
  memory 
  "build a memory for this test; a ByteArray of 1024 bytes, filled with NOPs"
+ 	| mem nop|
+ 	nop := CogARMCompiler new mov: 0  rn: 0.
- 	| mem |
  	mem := ByteArray new: 1024.
  	1 to: 1024  by: 4do:[:i|
+ 		mem unsignedLongAt: i put: nop bigEndian: false].
- 		mem unsignedLongAt: i put: 16rE1A00000 bigEndian: false].
  	^mem!

Item was changed:
  ----- Method: GdbARMAlienTests>>testDisassembling (in category 'tests') -----
  testDisassembling
  	"self new testDisassembling"
  
  	| memory result |
  	memory := WordArray new: 2.
+ 	memory at: 1 put:  (CogARMCompiler new add: 15 rn: 10 imm: 100 ror:0).
- 	memory at: 1 put: 3800756324.
  	result := self processor
  		disassembleInstructionAt: 0 
  		In: memory 
  		into: [:str :len | 
  			self 
  				assert: len = 4;
  				assert: str = '00000000: add	pc, sl, #100	; 0x64'].!

Item was changed:
  ----- Method: GdbARMAlienTests>>testLongJumpAddressForming (in category 'tests') -----
  testLongJumpAddressForming
  	"self new testLongJumpAddressForming"
  	"test of the somewhat loopy code used in CogARMCompiler>concretizeConditionalJumpLong: to generate the oading of a long address for jumps"
  	| memory |
  	memory := self memory.
  	self processor reset.
  	memory unsignedLongAt: 1 put: (CogARMCompiler new mov: 10 imm: 16r7F ror: 8)  bigEndian: false. 
  	memory unsignedLongAt: 5 put: (CogARMCompiler new orr: 10 imm: 16rFF ror: 16) bigEndian: false.
  	memory unsignedLongAt: 9 put: (CogARMCompiler new orr: 10 imm: 16rFE ror: 24) bigEndian: false. 
  	memory unsignedLongAt: 13 put: (CogARMCompiler new orr: 10 imm: 16r68 ror: 0) bigEndian: false. 
  
  	self processor
  		disassembleInstructionAt: 0 
  		In: memory 
  		into: [:str :len | 
  			self 
  				assert: len = 4;
  				assert: str equals: '00000000: mov	sl, #2130706432	; 0x7f000000'].
  	self processor
  		disassembleInstructionAt: 4 
  		In: memory 
  		into: [:str :len | 
  			self 
  				assert: len = 4;
  				assert: str equals: '00000004: orr	sl, sl, #16711680	; 0xff0000'].
  	self processor
  		disassembleInstructionAt: 8 
  		In: memory 
  		into: [:str :len | 
  			self 
  				assert: len = 4;
  				assert: str equals: '00000008: orr	sl, sl, #65024	; 0xfe00'].
  	self processor
  		disassembleInstructionAt: 12 
  		In: memory 
  		into: [:str :len | 
  			self 
  				assert: len = 4;
  				assert: str equals: '0000000c: orr	sl, sl, #104	; 0x68'].
  	self processor
  		pc: 0;
  		singleStepIn: memory;
  		singleStepIn: memory;
  		singleStepIn: memory;
  		singleStepIn: memory.
  	self 
  		assert: self processor pc = 16;
+ 		assert: self processor sl = 16r7FFFFE68;
- 		assert: self processor r10 = 16r7FFFFE68;
  		assert: self processor zflag = 0;
  		assert: self processor cflag = 0;
  		assert: self processor vflag = 0;
  		assert: self processor nflag = 0.
  !

Item was changed:
  ----- Method: GdbARMAlienTests>>testMoveRAw (in category 'tests') -----
  testMoveRAw
  	"Write a register to a constant address that is in-range."
  	
  	"self new testMoveRAw"
  	| memory |
  	memory := self memory.
  	self processor reset.
  
  	"LEA sl, #16r3FC"
  	memory unsignedLongAt: 5 put: (CogARMCompiler new mov: 10 imm: 0 ror: 0)  bigEndian: false. 
  	memory unsignedLongAt: 9 put: (CogARMCompiler new orr: 10 imm: 0 ror: 0) bigEndian: false.
  	memory unsignedLongAt: 13 put: (CogARMCompiler new orr: 10 imm: 2 ror: 24) bigEndian: false. 
  	memory unsignedLongAt: 17 put: (CogARMCompiler new orr: 10 imm: 40 ror: 0) bigEndian: false. 
  	"STR R5, [sl]"
  	memory unsignedLongAt: 21 put: (CogARMCompiler new str: 5 rn: 10 plusImm: 0) bigEndian: false.
  
  	
  	"processor disassembleFrom: 0 to: 60 in: memory on: Transcript cr"
  	self processor
  			pc: 4;
  			sp: (memory size - 4); "Room for return address"
  			r5: 99;
  			singleStepIn: memory readExecuteOnlyBelow: memory size / 2.
  			"We have to step several times, because the first step only changes the pc, but does not fetch anything from the address it points to."
  	self processor singleStepIn: memory readExecuteOnlyBelow: memory size / 2.
  	self processor singleStepIn: memory readExecuteOnlyBelow: memory size / 2.
  	self processor singleStepIn: memory readExecuteOnlyBelow: memory size / 2.
  	self processor singleStepIn: memory readExecuteOnlyBelow: memory size / 2.
  	self processor singleStepIn: memory readExecuteOnlyBelow: memory size / 2.
+ 	self assert:[(memory unsignedLongAt: (processor sl) + 1) = processor r5]
- 	self assert:[(memory unsignedLongAt: (processor r10) + 1) = processor r5]
  !

Item was changed:
  ----- Method: GdbARMAlienTests>>testQuickDisassemby (in category 'tests') -----
  testQuickDisassemby
  	"self new testQuickDisassemby"
  
  	| memory result |
  	memory := WordArray new: 2.
+ 	memory at: 1 put: (CogARMCompiler new orr: 6  imm: 16r3F ror: 16).
- 	memory at: 1 put: 3858758348.
  	result := self processor
  		disassembleInstructionAt: 0 
  		In: memory 
  		into: [:str :len | 
+ 			^str =  '00000000: orr	r6, r6, #4128768	; 0x3f0000'].!
- 			^str].!



More information about the Vm-dev mailing list