[Vm-dev] VM Maker: VMMaker.oscog-tpr.1233.mcz

commits at source.squeak.org commits at source.squeak.org
Tue Apr 21 22:00:00 UTC 2015


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

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

Name: VMMaker.oscog-tpr.1233
Author: tpr
Time: 21 April 2015, 2:56:01.578 pm
UUID: 56dee307-7a91-489a-865d-e11a267b7bf3
Ancestors: VMMaker.oscog-eem.1232

Fix a couple of places where the change to a word array of machine code needed compensating changes.

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

Item was changed:
  ----- Method: CogARMCompiler>>concretizeAlignmentNops (in category 'generate machine code - concretize') -----
  concretizeAlignmentNops
  	<inline: true>
  	"fill any slots with NOPs - in this case mov  r0, r0 - which is the NOP I always used to use"
  	self assert: machineCodeSize \\ 4 = 0.
  	0 to: machineCodeSize - 1 by: 4 do:
+ 		[:p| self machineCodeAt: p put: 16rE1A00000]!
- 		[:p| machineCode at: p put: 16rE1A00000]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeConditionalInstruction (in category 'generate machine code') -----
  concretizeConditionalInstruction
  	"Concretize the current instruction, but with a condition."
  	<returnTypeC: #void>
  	| savedCond |
  	self assert: cond notNil.
  	savedCond := cond.
  	cond := nil.
  	self dispatchConcretize.
  	cond := savedCond.
+ 	0 to: machineCodeSize-1 by: 4 do:
+ 		[:i| | instr |
+ 		instr := (self machineCodeAt: i) bitClear: 16rF<<28.
+ 		self machineCodeAt: i put: (instr bitOr: (cond bitAnd: 16rF)<<28)]!
- 	3 to: machineCodeSize by: 4 do:
- 		[:i| | topByte |
- 		 topByte := machineCode at: i.
- 		 self assert: (topByte bitClear: 15) = 0.
- 		 machineCode at: i put: cond << 4 + topByte]!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeFill32 (in category 'generate machine code') -----
  concretizeFill32
  	"fill with operand 0 according to the processor's endianness"
  	| word |
  	<var: #word type: #'unsigned long'>
  	word := operands at: 0.
+ 	self machineCodeAt: 0 put: word.
- 	machineCode at: 0 put: (word bitAnd: 16rFF).
- 	machineCode at: 1 put: (word >> 8bitAnd: 16rFF)..
- 	machineCode at: 2 put: (word >> 16bitAnd: 16rFF)..
- 	machineCode at: 3 put: (word >> 24bitAnd: 16rFF)..
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogARMCompiler>>concretizeStop (in category 'generate machine code - concretize') -----
  concretizeStop
  "generate a BKPT instruction. We could, given a good enough creative impulse and an over-active sense of humour, add some numerically encoded witticism to this instruction in bits 8-19 & 0-3. It has no effect on the execution but can be a way to specify which breakpoint has been hit etc."
  	<inline: true>
+ 	self machineCodeAt: 0 put: (AL <<28 bitOr: (16r42 <<20 bitOr:(7<<4))).
- 	machineCode at: 0 put: (AL <<28 bitOr: (16r42 <<20 bitOr:(7<<4))).
  	^machineCodeSize := 4!

Item was changed:
  ----- Method: CogAbstractInstruction>>printStateOn: (in category 'printing') -----
  printStateOn: aStream
  	| opcodeName orneryOperands format |
  	<doNotGenerate> "Smalltalk-side only"
  	opcode isNil ifTrue:
  		[^self].
  	aStream space; nextPut: $(; nextPutAll: (opcodeName := self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	(cogit isKindOf: Cogit) ifTrue:
  		[format := CogRTLOpcodes printFormatForOpcodeName: opcodeName].
  	orneryOperands withIndexDo:
  		[:operand :index|
  		operand notNil ifTrue:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 (format notNil and: [(format at: index ifAbsent: nil) = $r])
  				ifTrue: [aStream nextPutAll: (self nameForRegister: operand)]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16 and: [opcode ~= Label]]) ifTrue:
  						[(operand allMask: 16r80000000) ifTrue:
  							[aStream nextPut: $/; print: operand signedIntFromLong].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16]]]].
  	machineCodeSize ifNotNil:
  		[(machineCodeSize between: 1 and: machineCode size) ifTrue:
+ 			[0 to: machineCodeSize - 1 by: self codeGranularity do:
- 			[0 to: machineCodeSize - 1 do:
  				[:i|
  				 aStream space.
+ 				 (self machineCodeAt: i) printOn: aStream base: 16]]].
- 				 (machineCode at: i) printOn: aStream base: 16]]].
  	address ifNotNil:
  		[aStream nextPut: $@.
  		 address printOn: aStream base: 16].
  	aStream nextPut: $)!

Item was changed:
  ----- Method: CogAbstractInstruction>>symbolicOn: (in category 'printing') -----
  symbolicOn: aStream
  	| orneryOperands |
  	<doNotGenerate> "Smalltalk-side only"
  	(machineCodeSize isNil
  	 or: [opcode = 16rAAA]) ifTrue:
  		[^aStream nextPut: 'uninitialized opcode'].
  	aStream space; nextPut: $(; nextPutAll: (self class nameForOpcode: opcode).
  	orneryOperands := operands isCObjectAccessor
  							ifTrue: [operands object]
  							ifFalse: [operands].
  	orneryOperands withIndexDo:
  		[:operand :index|
  		operand notNil ifTrue:
  			[aStream space.
  			 index >= (orneryOperands identityIndexOf: nil ifAbsent: [orneryOperands size + 1]) ifTrue:
  				[aStream print: index - 1; nextPut: $:].
  			 operand class == self class
  				ifTrue:
  					[operand symbolicOn: aStream]
  				ifFalse:
  					[aStream print: operand.
  					 (operand isInteger and: [operand > 16]) ifTrue:
  						[(operand allMask: 16r80000000) ifTrue:
  							[aStream nextPut: $/; print: operand signedIntFromLong].
  						 aStream nextPut: $/.
  						 operand printOn: aStream base: 16]]]].
  	machineCodeSize > 0 ifTrue:
  		[machineCodeSize > machineCode size
  			ifTrue: [aStream nextPutAll: ' no mcode']
  			ifFalse:
+ 				[0 to: machineCodeSize - 1 by: self codeGranularity do:
- 				[0 to: machineCodeSize - 1 do:
  					[:i|
  					 aStream space.
+ 					 (self machineCodeAt: i) printOn: aStream base: 16]]].
- 					 (machineCode at: i) printOn: aStream base: 16]]].
  	aStream nextPut: $)!



More information about the Vm-dev mailing list