[Vm-dev] VM Maker: VMMaker.oscog-eem.300.mcz

commits at source.squeak.org commits at source.squeak.org
Fri Jun 21 23:36:56 UTC 2013


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

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

Name: VMMaker.oscog-eem.300
Author: eem
Time: 21 June 2013, 4:34:38.785 pm
UUID: b52f5f3d-b4e2-4bfb-ba9a-a6b55c71a8d3
Ancestors: VMMaker.oscog-eem.299

Fix type errors in the Cogit that prevent the Cogit working when
compiled with clang.  Specifically void * pointers are not comparable.
Make sure that fetchPointer:ofObject: & isIntegerValue: are declared
in cointerp.h.

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

Item was changed:
  ----- Method: CogARMCompiler>>sizePCDependentInstructionAt: (in category 'generate machine code') -----
  sizePCDependentInstructionAt: eventualAbsoluteAddress
  	"Size a jump and set its address.  The target may be another instruction
  	 or an absolute address.  On entry the address inst var holds our virtual
  	 address. On exit address is set to eventualAbsoluteAddress, which is
  	 where this instruction will be output.  The span of a jump to a following
  	 instruction is therefore between that instruction's address and this
  	 instruction's address ((which are both still their virtual addresses), but the
  	 span of a jump to a preceeding instruction or to an absolute address is
  	 between that instruction's address (which by now is its eventual absolute
  	 address) or absolute address and eventualAbsoluteAddress."
  
+ 	| target maximumSpan abstractInstruction |
- 	| target maximumSpan |
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	opcode = AlignmentNops ifTrue:
  		[| alignment |
  		 address := eventualAbsoluteAddress.
  		 alignment := operands at: 0.
  		 ^machineCodeSize := (eventualAbsoluteAddress + (alignment - 1) bitAnd: alignment negated)
  							   - eventualAbsoluteAddress].
  	self assert: (self isJump or: [opcode = Call]).
  	self isJump ifTrue: [self resolveJumpTarget].
  	target := operands at: 0.
+ 	abstractInstruction := cogit cCoerceSimple: target to: #'AbstractInstruction *'.
  	"maximumSpan calculation copied from CogIA32Compiler TODO: extract method?"
+ 	(self isAnInstruction: abstractInstruction)
- 	(self isAnInstruction: (cogit cCoerceSimple: target to: #'void *'))
  		ifTrue:
+ 			[maximumSpan := abstractInstruction address
- 			[| abstractInstruction |
- 			abstractInstruction := cogit cCoerceSimple: target to: #'AbstractInstruction *'.
- 			maximumSpan := abstractInstruction address
  							- (((cogit abstractInstruction: self follows: abstractInstruction)
  								ifTrue: [eventualAbsoluteAddress]
  								ifFalse: [address]) + 2)]
  		ifFalse:
  			[maximumSpan := target - (eventualAbsoluteAddress + 2)].
  	address := eventualAbsoluteAddress.
  	^machineCodeSize := opcode = Call 
  				ifTrue: [(self isQuick: maximumSpan) ifTrue: [4] ifFalse: [20]]
  				ifFalse: [(self isLongJump not and: [self isQuick: maximumSpan])
  								ifTrue: [4]
  								ifFalse: [16]] "load address to register, add"!

Item was changed:
  ----- Method: CogARMCompilerTests>>assertSaneJumpTarget: (in category 'cogit compiler compatibility') -----
  assertSaneJumpTarget: jumpTarget
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 	<var: #jumpTarget type: #'void *'>
  
  	self assert: (self addressIsInInstructions: jumpTarget)!

Item was changed:
  ----- Method: CogAbstractInstruction>>isAnInstruction: (in category 'testing') -----
  isAnInstruction: addressOrInstruction
+ 	<var: #addressOrInstruction type: #'AbstractInstruction *'>
- 	<var: #addressOrInstruction type: #'void *'>
  	^cogit addressIsInInstructions: addressOrInstruction!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveAwR (in category 'generate machine code') -----
  concretizeMoveAwR
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg |
  	addressOperand := operands at: 0.
+ 	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
- 	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'void *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg := self concreteRegister: (operands at: 1).
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16rA1;
  			at: 1 put: (addressOperand bitAnd: 16rFF);
  			at: 2 put: (addressOperand >> 8 bitAnd: 16rFF);
  			at: 3 put: (addressOperand >> 16 bitAnd: 16rFF);
  			at: 4 put: (addressOperand >> 24 bitAnd: 16rFF).
  			^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r8B;
  		at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 2 put: (addressOperand bitAnd: 16rFF);
  		at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
  	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>concretizeMoveRAw (in category 'generate machine code') -----
  concretizeMoveRAw
  	"Will get inlined into concretizeAt: switch."
  	<inline: true>
  	| addressOperand reg |
  	reg := self concreteRegister: (operands at: 0).
  	addressOperand := operands at: 1.
+ 	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *')) ifTrue:
- 	(self isAnInstruction: (cogit cCoerceSimple: addressOperand to: #'void *')) ifTrue:
  		[addressOperand := (cogit cCoerceSimple: addressOperand to: #'AbstractInstruction *') address].
  	reg = EAX ifTrue:
  		[machineCode
  			at: 0 put: 16rA3;
  			at: 1 put: (addressOperand bitAnd: 16rFF);
  			at: 2 put: (addressOperand >> 8 bitAnd: 16rFF);
  			at: 3 put: (addressOperand >> 16 bitAnd: 16rFF);
  			at: 4 put: (addressOperand >> 24 bitAnd: 16rFF).
  			^machineCodeSize := 5].
  	machineCode
  		at: 0 put: 16r89;
  		at: 1 put: (self mod: ModRegInd RM: 5 RO: reg);
  		at: 2 put: (addressOperand bitAnd: 16rFF);
  		at: 3 put: (addressOperand >> 8 bitAnd: 16rFF);
  		at: 4 put: (addressOperand >> 16 bitAnd: 16rFF);
  		at: 5 put: (addressOperand >> 24 bitAnd: 16rFF).
  	^machineCodeSize := 6!

Item was changed:
  ----- Method: CogIA32Compiler>>sizePCDependentInstructionAt: (in category 'generate machine code') -----
  sizePCDependentInstructionAt: eventualAbsoluteAddress
  	"Size a jump and set its address.  The target may be another instruction
  	 or an absolute address.  On entry the address inst var holds our virtual
  	 address. On exit address is set to eventualAbsoluteAddress, which is
  	 where this instruction will be output.  The span of a jump to a following
  	 instruction is therefore between that instruction's address and this
  	 instruction's address ((which are both still their virtual addresses), but the
  	 span of a jump to a preceeding instruction or to an absolute address is
  	 between that instruction's address (which by now is its eventual absolute
  	 address) or absolute address and eventualAbsoluteAddress."
  
+ 	| target maximumSpan abstractInstruction |
- 	| target maximumSpan |
  	<var: #abstractInstruction type: #'AbstractInstruction *'>
  	opcode = AlignmentNops ifTrue:
  		[| alignment |
  		 address := eventualAbsoluteAddress.
  		 alignment := operands at: 0.
  		 ^machineCodeSize := (eventualAbsoluteAddress + (alignment - 1) bitAnd: alignment negated)
  							   - eventualAbsoluteAddress].
  	self assert: self isJump.
  	target := operands at: 0.
+ 	abstractInstruction := cogit cCoerceSimple: target to: #'AbstractInstruction *'.
+ 	(self isAnInstruction: abstractInstruction)
- 	(self isAnInstruction: (cogit cCoerceSimple: target to: #'void *'))
  		ifTrue:
+ 			[maximumSpan := abstractInstruction address
- 			[| abstractInstruction |
- 			abstractInstruction := cogit cCoerceSimple: target to: #'AbstractInstruction *'.
- 			maximumSpan := abstractInstruction address
  							- (((cogit abstractInstruction: self follows: abstractInstruction)
  								ifTrue: [eventualAbsoluteAddress]
  								ifFalse: [address]) + 2)]
  		ifFalse:
  			[maximumSpan := target - (eventualAbsoluteAddress + 2)].
  	address := eventualAbsoluteAddress.
  	^machineCodeSize := opcode >= FirstShortJump
  							ifTrue:
  								[(self isQuick: maximumSpan)
  									ifTrue: [2]
  									ifFalse: [opcode = Jump
  												ifTrue: [5]
  												ifFalse: [6]]]
  							ifFalse:
  								[opcode = JumpLong
  									ifTrue: [5]
  									ifFalse: [6]]!

Item was changed:
  ----- Method: CogIA32CompilerTests>>assertSaneJumpTarget: (in category 'cogit compatibility') -----
  assertSaneJumpTarget: jumpTarget
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 	<var: #jumpTarget type: #'void *'>
  
  	self assert: (self addressIsInInstructions: jumpTarget)!

Item was changed:
  ----- Method: CogMethodZone>>methodFor: (in category 'jit - api') -----
  methodFor: address
  	<api>
  	<returnTypeC: #'CogMethod *'>
  	<var: #address type: #'void *'>
  	| cogMethod nextMethod |
  	<var: #cogMethod type: #'CogMethod *'>
  	<var: #nextMethod type: #'CogMethod *'>
  	cogMethod := coInterpreter cCoerceSimple: baseAddress to: #'CogMethod *'.
  	[cogMethod < self limitZony
+ 	 and: [cogMethod asUnsignedInteger <= address asUnsignedInteger]] whileTrue:
- 	 and: [(self cCoerceSimple: cogMethod to: #'void *') <= address]] whileTrue:
  		[nextMethod := self methodAfter: cogMethod.
  		 nextMethod = cogMethod ifTrue:
  			[^0].
+ 		 (address asUnsignedInteger >= cogMethod asUnsignedInteger
+ 		  and: [address asUnsignedInteger < nextMethod asUnsignedInteger]) ifTrue:
- 		 (address >= (self cCoerceSimple: cogMethod to: #'void *')
- 		  and: [address < (self cCoerceSimple: nextMethod to: #'void *')]) ifTrue:
  			[^cogMethod].
  		 cogMethod := nextMethod].
  	^0!

Item was changed:
  ----- Method: Cogit>>addressIsInFixups: (in category 'testing') -----
  addressIsInFixups: address
+ 	<var: #address type: #'AbstractInstruction *'>
+ 	^self cCode: 'address >= (AbstractInstruction *)&fixups[0] && address < (AbstractInstruction *)&fixups[numAbstractOpcodes]'
- 	<var: #address type: #'void *'>
- 	^self cCode: 'address >= (void *)&fixups[0] && address < (void *)&fixups[numAbstractOpcodes]'
  		inSmalltalk: [fixups notNil
  					and: [(fixups object identityIndexOf: address) between: 1 and: numAbstractOpcodes]]!

Item was changed:
  ----- Method: Cogit>>addressIsInInstructions: (in category 'testing') -----
  addressIsInInstructions: address
+ 	<var: #address type: #'AbstractInstruction *'>
+ 	^self cCode: 'address >= &abstractOpcodes[0] && address < &abstractOpcodes[opcodeIndex]'
- 	<var: #address type: #'void *'>
- 	^self cCode: 'address >= (void *)&abstractOpcodes[0] && address < (void *)&abstractOpcodes[opcodeIndex]'
  		inSmalltalk: [(abstractOpcodes object identityIndexOf: address) between: 1 and: opcodeIndex]!

Item was changed:
  ----- Method: Cogit>>assertSaneJumpTarget: (in category 'debugging') -----
  assertSaneJumpTarget: jumpTarget
+ 	<var: #jumpTarget type: #'AbstractInstruction *'>
- 	<var: #jumpTarget type: #'void *'>
  
  	self assert: (closedPICSize isNil "don't whinge when producing the PIC prototypes"
  			or: [openPICSize isNil
  			or: [(self addressIsInInstructions: jumpTarget)
+ 			or: [(jumpTarget asUnsignedInteger
- 			or: [(jumpTarget asInteger
  					between: codeBase
  					and: methodZone limitZony asInteger + (closedPICSize max: openPICSize))]]])!

Item was changed:
  ----- Method: ObjectMemory>>fetchPointer:ofObject: (in category 'interpreter access') -----
  fetchPointer: fieldIndex ofObject: oop
  	"index by word size, and return a pointer as long as the word size"
+ 	<api>
+ 	^self longAt: oop + BaseHeaderSize + (fieldIndex << ShiftForWord)!
- 
- 	^ self longAt: oop + BaseHeaderSize + (fieldIndex << ShiftForWord)!

Item was changed:
  ----- Method: ObjectMemory>>isIntegerValue: (in category 'interpreter access') -----
  isIntegerValue: intValue
  	"Answer if the given value can be represented as a Smalltalk integer value.
  	 In C, use a shift and XOR to set the sign bit if and only if the top two bits of the given
  	 value are the same, then test the sign bit. Note that the top two bits are equal for
  	 exactly those integers in the range that can be represented in 31-bits or 63-bits."
+ 	<api>
- 
  	^self
  		cCode: [(intValue bitXor: (intValue << 1)) >= 0]
  		inSmalltalk: [intValue >= 16r-40000000 and: [intValue <= 16r3FFFFFFF]]!

Item was changed:
  ----- Method: SistaStackToRegisterMappingCogit>>addressIsInInstructions: (in category 'testing') -----
  addressIsInInstructions: address
+ 	<var: #address type: #'AbstractInstruction *'>
- 	<var: #address type: #'void *'>
  	^self cCode:
+ 			'address >= &abstractOpcodes[0] && address < &abstractOpcodes[opcodeIndex]
+ 			|| address >= &counters[0] && address < &counters[counterIndex]'
- 			'address >= (void *)&abstractOpcodes[0] && address < (void *)&abstractOpcodes[opcodeIndex]
- 			|| address >= (void *)&counters[0] && address < (void *)&counters[counterIndex]'
  		inSmalltalk:
  			[((abstractOpcodes object identityIndexOf: address) between: 1 and: opcodeIndex)
  			or: [(counters object identityIndexOf: address) between: 1 and: counterIndex]]!



More information about the Vm-dev mailing list